X-Git-Url: http://repo.macrolet.net/gitweb/?a=blobdiff_plain;f=src%2Fcode%2Fcondition.lisp;h=29c854a2b3f380e728a003895527157a5db0bf50;hb=f3f677703e37f5a335b3be7fa64f7748ad969517;hp=01421bbb164ad656d010b97646bd2f9216f481db;hpb=38f18f2eb2a1d66d2c138a2f5e10e6be93aacb1b;p=sbcl.git diff --git a/src/code/condition.lisp b/src/code/condition.lisp index 01421bb..29c854a 100644 --- a/src/code/condition.lisp +++ b/src/code/condition.lisp @@ -13,6 +13,26 @@ (in-package "SB!KERNEL") +;;;; miscellaneous support utilities + +;;; Signalling an error when trying to print an error condition is +;;; generally a PITA, so whatever the failure encountered when +;;; wondering about FILE-POSITION within a condition printer, 'tis +;;; better silently to give up than to try to complain. +(defun file-position-or-nil-for-error (stream &optional (pos nil posp)) + ;; Arguably FILE-POSITION shouldn't be signalling errors at all; but + ;; "NIL if this cannot be determined" in the ANSI spec doesn't seem + ;; absolutely unambiguously to prohibit errors when, e.g., STREAM + ;; has been closed so that FILE-POSITION is a nonsense question. So + ;; my (WHN) impression is that the conservative approach is to + ;; IGNORE-ERRORS. (I encountered this failure from within a homebrew + ;; defsystemish operation where the ERROR-STREAM had been CL:CLOSEd, + ;; I think by nonlocally exiting through a WITH-OPEN-FILE, by the + ;; time an error was reported.) + (if posp + (ignore-errors (file-position stream pos)) + (ignore-errors (file-position stream)))) + ;;;; the CONDITION class (/show0 "condition.lisp 20") @@ -233,8 +253,7 @@ "Make an instance of a condition object using the specified initargs." ;; Note: ANSI specifies no exceptional situations in this function. ;; signalling simple-type-error would not be wrong. - (let* ((thing (if (symbolp thing) - (find-classoid thing) + (let* ((thing (or (and (symbolp thing) (find-classoid thing nil)) thing)) (class (typecase thing (condition-classoid thing) @@ -266,54 +285,58 @@ (return nil))) (setf (getf (condition-assigned-slots res) (condition-slot-name hslot)) (find-slot-default class hslot)))) - res)) ;;;; DEFINE-CONDITION (eval-when (:compile-toplevel :load-toplevel :execute) -(defun %compiler-define-condition (name direct-supers layout) - (multiple-value-bind (class old-layout) - (insured-find-classoid name - #'condition-classoid-p - #'make-condition-classoid) - (setf (layout-classoid layout) class) - (setf (classoid-direct-superclasses class) - (mapcar #'find-classoid direct-supers)) - (cond ((not old-layout) - (register-layout layout)) - ((not *type-system-initialized*) - (setf (layout-classoid old-layout) class) - (setq layout old-layout) - (unless (eq (classoid-layout class) layout) +(defun %compiler-define-condition (name direct-supers layout + all-readers all-writers) + (with-single-package-locked-error + (:symbol name "defining ~A as a condition") + (sb!xc:proclaim `(ftype (function (t) t) ,@all-readers)) + (sb!xc:proclaim `(ftype (function (t t) t) ,@all-writers)) + (multiple-value-bind (class old-layout) + (insured-find-classoid name + #'condition-classoid-p + #'make-condition-classoid) + (setf (layout-classoid layout) class) + (setf (classoid-direct-superclasses class) + (mapcar #'find-classoid direct-supers)) + (cond ((not old-layout) + (register-layout layout)) + ((not *type-system-initialized*) + (setf (layout-classoid old-layout) class) + (setq layout old-layout) + (unless (eq (classoid-layout class) layout) + (register-layout layout))) + ((redefine-layout-warning "current" + old-layout + "new" + (layout-length layout) + (layout-inherits layout) + (layout-depthoid layout) + (layout-n-untagged-slots layout)) + (register-layout layout :invalidate t)) + ((not (classoid-layout class)) (register-layout layout))) - ((redefine-layout-warning "current" - old-layout - "new" - (layout-length layout) - (layout-inherits layout) - (layout-depthoid layout)) - (register-layout layout :invalidate t)) - ((not (classoid-layout class)) - (register-layout layout))) - - (setf (layout-info layout) - (locally - ;; KLUDGE: There's a FIND-CLASS DEFTRANSFORM for constant class - ;; names which creates fast but non-cold-loadable, non-compact - ;; code. In this context, we'd rather have compact, cold-loadable - ;; code. -- WHN 19990928 - (declare (notinline find-classoid)) - (layout-info (classoid-layout (find-classoid 'condition))))) - - (setf (find-classoid name) class) - - ;; Initialize CPL slot. - (setf (condition-classoid-cpl class) - (remove-if-not #'condition-classoid-p - (std-compute-class-precedence-list class)))) + + (setf (layout-info layout) + (locally + ;; KLUDGE: There's a FIND-CLASS DEFTRANSFORM for constant class + ;; names which creates fast but non-cold-loadable, non-compact + ;; code. In this context, we'd rather have compact, cold-loadable + ;; code. -- WHN 19990928 + (declare (notinline find-classoid)) + (layout-info (classoid-layout (find-classoid 'condition))))) + + (setf (find-classoid name) class) + + ;; Initialize CPL slot. + (setf (condition-classoid-cpl class) + (remove-if-not #'condition-classoid-p + (std-compute-class-precedence-list class))))) (values)) - ) ; EVAL-WHEN ;;; Compute the effective slots of CLASS, copying inherited slots and @@ -365,49 +388,53 @@ (lambda (new-value condition) (condition-writer-function condition new-value slot-name)))) -(defun %define-condition (name slots documentation report default-initargs) - (let ((class (find-classoid name))) - (setf (condition-classoid-slots class) slots) - (setf (condition-classoid-report class) report) - (setf (condition-classoid-default-initargs class) default-initargs) - (setf (fdocumentation name 'type) documentation) - - (dolist (slot slots) - - ;; Set up reader and writer functions. - (let ((slot-name (condition-slot-name slot))) - (dolist (reader (condition-slot-readers slot)) - (install-condition-slot-reader reader name slot-name)) - (dolist (writer (condition-slot-writers slot)) - (install-condition-slot-writer writer name slot-name)))) - - ;; Compute effective slots and set up the class and hairy slots - ;; (subsets of the effective slots.) - (let ((eslots (compute-effective-slots class)) - (e-def-initargs - (reduce #'append - (mapcar #'condition-classoid-default-initargs +(defun %define-condition (name parent-types layout slots documentation + report default-initargs all-readers all-writers) + (with-single-package-locked-error + (:symbol name "defining ~A as a condition") + (%compiler-define-condition name parent-types layout all-readers all-writers) + (let ((class (find-classoid name))) + (setf (condition-classoid-slots class) slots) + (setf (condition-classoid-report class) report) + (setf (condition-classoid-default-initargs class) default-initargs) + (setf (fdocumentation name 'type) documentation) + + (dolist (slot slots) + + ;; Set up reader and writer functions. + (let ((slot-name (condition-slot-name slot))) + (dolist (reader (condition-slot-readers slot)) + (install-condition-slot-reader reader name slot-name)) + (dolist (writer (condition-slot-writers slot)) + (install-condition-slot-writer writer name slot-name)))) + + ;; Compute effective slots and set up the class and hairy slots + ;; (subsets of the effective slots.) + (let ((eslots (compute-effective-slots class)) + (e-def-initargs + (reduce #'append + (mapcar #'condition-classoid-default-initargs (condition-classoid-cpl class))))) - (dolist (slot eslots) - (ecase (condition-slot-allocation slot) - (:class - (unless (condition-slot-cell slot) - (setf (condition-slot-cell slot) - (list (if (condition-slot-initform-p slot) - (let ((initform (condition-slot-initform slot))) - (if (functionp initform) - (funcall initform) - initform)) - *empty-condition-slot*)))) - (push slot (condition-classoid-class-slots class))) - ((:instance nil) - (setf (condition-slot-allocation slot) :instance) - (when (or (functionp (condition-slot-initform slot)) - (dolist (initarg (condition-slot-initargs slot) nil) - (when (functionp (getf e-def-initargs initarg)) - (return t)))) - (push slot (condition-classoid-hairy-slots class)))))))) - name) + (dolist (slot eslots) + (ecase (condition-slot-allocation slot) + (:class + (unless (condition-slot-cell slot) + (setf (condition-slot-cell slot) + (list (if (condition-slot-initform-p slot) + (let ((initform (condition-slot-initform slot))) + (if (functionp initform) + (funcall initform) + initform)) + *empty-condition-slot*)))) + (push slot (condition-classoid-class-slots class))) + ((:instance nil) + (setf (condition-slot-allocation slot) :instance) + (when (or (functionp (condition-slot-initform slot)) + (dolist (initarg (condition-slot-initargs slot) nil) + (when (functionp (getf e-def-initargs initarg)) + (return t)))) + (push slot (condition-classoid-hairy-slots class)))))))) + name)) (defmacro define-condition (name (&rest parent-types) (&rest slot-specs) &body options) @@ -522,17 +549,19 @@ (error "unknown option: ~S" (first option))))) `(progn - (eval-when (:compile-toplevel :load-toplevel :execute) - (%compiler-define-condition ',name ',parent-types ',layout)) - - (declaim (ftype (function (t) t) ,@(all-readers))) - (declaim (ftype (function (t t) t) ,@(all-writers))) - - (%define-condition ',name - (list ,@(slots)) - ,documentation - ,report - (list ,@default-initargs)))))) + (eval-when (:compile-toplevel) + (%compiler-define-condition ',name ',parent-types ',layout + ',(all-readers) ',(all-writers))) + (eval-when (:load-toplevel :execute) + (%define-condition ',name + ',parent-types + ',layout + (list ,@(slots)) + ,documentation + ,report + (list ,@default-initargs) + ',(all-readers) + ',(all-writers))))))) ;;;; DESCRIBE on CONDITIONs @@ -577,6 +606,9 @@ (define-condition simple-error (simple-condition error) ()) +;;; not specified by ANSI, but too useful not to have around. +(define-condition simple-style-warning (simple-condition style-warning) ()) + (define-condition storage-condition (serious-condition) ()) (define-condition type-error (error) @@ -678,20 +710,32 @@ (:report (lambda (condition stream) (let* ((error-stream (stream-error-stream condition)) - (pos (file-position error-stream))) + (pos (file-position-or-nil-for-error error-stream))) (let (lineno colno) (when (and pos (< pos sb!xc:array-dimension-limit) + ;; KLUDGE: lseek() (which is what FILE-POSITION + ;; reduces to on file-streams) is undefined on + ;; "some devices", which in practice means that it + ;; can claim to succeed on /dev/stdin on Darwin + ;; and Solaris. This is obviously bad news, + ;; because the READ-SEQUENCE below will then + ;; block, not complete, and the report will never + ;; be printed. As a workaround, we exclude + ;; interactive streams from this attempt to report + ;; positions. -- CSR, 2003-08-21 + (not (interactive-stream-p error-stream)) (file-position error-stream :start)) (let ((string (make-string pos - :element-type (stream-element-type error-stream)))) + :element-type (stream-element-type + error-stream)))) (when (= pos (read-sequence string error-stream)) (setq lineno (1+ (count #\Newline string)) colno (- pos - (or (position #\Newline string :from-end t) 0) + (or (position #\Newline string :from-end t) -1) 1)))) - (file-position error-stream pos)) + (file-position-or-nil-for-error error-stream pos)) (format stream "READER-ERROR ~@[at ~W ~]~ ~@[(line ~W~]~@[, column ~W) ~]~ @@ -700,12 +744,253 @@ (reader-error-format-control condition) (reader-error-format-arguments condition))))))) +;;;; special SBCL extension conditions + +;;; an error apparently caused by a bug in SBCL itself +;;; +;;; Note that we don't make any serious effort to use this condition +;;; for *all* errors in SBCL itself. E.g. type errors and array +;;; indexing errors can occur in functions called from SBCL code, and +;;; will just end up as ordinary TYPE-ERROR or invalid index error, +;;; because the signalling code has no good way to know that the +;;; underlying problem is a bug in SBCL. But in the fairly common case +;;; that the signalling code does know that it's found a bug in SBCL, +;;; this condition is appropriate, reusing boilerplate and helping +;;; users to recognize it as an SBCL bug. +(define-condition bug (simple-error) + () + (:report + (lambda (condition stream) + (format stream + "~@< ~? ~:@_~?~:>" + (simple-condition-format-control condition) + (simple-condition-format-arguments condition) + "~@.~:@>" + '((fmakunbound 'compile)))))) + +(define-condition simple-storage-condition (storage-condition simple-condition) ()) + +;;; a condition for use in stubs for operations which aren't supported +;;; on some platforms +;;; +;;; E.g. in sbcl-0.7.0.5, it might be appropriate to do something like +;;; #-(or freebsd linux) +;;; (defun load-foreign (&rest rest) +;;; (error 'unsupported-operator :name 'load-foreign)) +;;; #+(or freebsd linux) +;;; (defun load-foreign ... actual definition ...) +;;; By signalling a standard condition in this case, we make it +;;; possible for test code to distinguish between (1) intentionally +;;; unimplemented and (2) unintentionally just screwed up somehow. +;;; (Before this condition was defined, test code tried to deal with +;;; this by checking for FBOUNDP, but that didn't work reliably. In +;;; sbcl-0.7.0, a a package screwup left the definition of +;;; LOAD-FOREIGN in the wrong package, so it was unFBOUNDP even on +;;; architectures where it was supposed to be supported, and the +;;; regression tests cheerfully passed because they assumed that +;;; unFBOUNDPness meant they were running on an system which didn't +;;; support the extension.) +(define-condition unsupported-operator (simple-error) ()) + + +;;; (:ansi-cl :function remove) +;;; (:ansi-cl :section (a b c)) +;;; (:ansi-cl :glossary "similar") +;;; +;;; (:sbcl :node "...") +;;; (:sbcl :variable *ed-functions*) +;;; +;;; FIXME: this is not the right place for this. +(defun print-reference (reference stream) + (ecase (car reference) + (:amop + (format stream "AMOP") + (format stream ", ") + (destructuring-bind (type data) (cdr reference) + (ecase type + (:generic-function (format stream "Generic Function ~S" data)) + (:section (format stream "Section ~{~D~^.~}" data))))) + (:ansi-cl + (format stream "The ANSI Standard") + (format stream ", ") + (destructuring-bind (type data) (cdr reference) + (ecase type + (:function (format stream "Function ~S" data)) + (:special-operator (format stream "Special Operator ~S" data)) + (:macro (format stream "Macro ~S" data)) + (:section (format stream "Section ~{~D~^.~}" data)) + (:glossary (format stream "Glossary entry for ~S" data)) + (:issue (format stream "writeup for Issue ~A" data))))) + (:sbcl + (format stream "The SBCL Manual") + (format stream ", ") + (destructuring-bind (type data) (cdr reference) + (ecase type + (:node (format stream "Node ~S" data)) + (:variable (format stream "Variable ~S" data)) + (:function (format stream "Function ~S" data))))) + ;; FIXME: other documents (e.g. CLIM, Franz documentation :-) + )) +(define-condition reference-condition () + ((references :initarg :references :reader reference-condition-references))) +(defvar *print-condition-references* t) +(def!method print-object :around ((o reference-condition) s) + (call-next-method) + (unless (or *print-escape* *print-readably*) + (when (and *print-condition-references* + (reference-condition-references o)) + (format s "~&See also:~%") + (pprint-logical-block (s nil :per-line-prefix " ") + (do* ((rs (reference-condition-references o) (cdr rs)) + (r (car rs) (car rs))) + ((null rs)) + (print-reference r s) + (unless (null (cdr rs)) + (terpri s))))))) + +(define-condition duplicate-definition (reference-condition warning) + ((name :initarg :name :reader duplicate-definition-name)) + (:report (lambda (c s) + (format s "~@" + (duplicate-definition-name c)))) + (:default-initargs :references (list '(:ansi-cl :section (3 2 2 3))))) + +(define-condition package-at-variance (reference-condition simple-warning) + () + (:default-initargs :references (list '(:ansi-cl :macro defpackage)))) + +(define-condition defconstant-uneql (reference-condition error) + ((name :initarg :name :reader defconstant-uneql-name) + (old-value :initarg :old-value :reader defconstant-uneql-old-value) + (new-value :initarg :new-value :reader defconstant-uneql-new-value)) + (:report + (lambda (condition stream) + (format stream + "~@" + (defconstant-uneql-name condition) + (defconstant-uneql-old-value condition) + (defconstant-uneql-new-value condition)))) + (:default-initargs :references (list '(:ansi-cl :macro defconstant) + '(:sbcl :node "Idiosyncrasies")))) + +(define-condition array-initial-element-mismatch + (reference-condition simple-warning) + () + (:default-initargs + :references (list + '(:ansi-cl :function make-array) + '(:ansi-cl :function sb!xc:upgraded-array-element-type)))) + +(define-condition displaced-to-array-too-small-error + (reference-condition simple-error) + () + (:default-initargs + :references (list '(:ansi-cl :function adjust-array)))) + +(define-condition type-warning (reference-condition simple-warning) + () + (:default-initargs :references (list '(:sbcl :node "Handling of Types")))) + +(define-condition local-argument-mismatch (reference-condition simple-warning) + () + (:default-initargs :references (list '(:ansi-cl :section (3 2 2 3))))) + +(define-condition format-args-mismatch (reference-condition) + () + (:default-initargs :references (list '(:ansi-cl :section (22 3 10 2))))) + +(define-condition format-too-few-args-warning + (format-args-mismatch simple-warning) + ()) +(define-condition format-too-many-args-warning + (format-args-mismatch simple-style-warning) + ()) + +(define-condition extension-failure (reference-condition simple-error) + ()) + +(define-condition structure-initarg-not-keyword + (reference-condition simple-style-warning) + () + (:default-initargs :references (list '(:ansi-cl :section (2 4 8 13))))) + +#!+sb-package-locks +(progn + +(define-condition package-lock-violation (reference-condition package-error) + ((format-control :initform nil :initarg :format-control + :reader package-error-format-control) + (format-arguments :initform nil :initarg :format-arguments + :reader package-error-format-arguments)) + (:report + (lambda (condition stream) + (let ((control (package-error-format-control condition))) + (if control + (apply #'format stream + (format nil "~~@" + (package-name (package-error-package condition)) + control) + (package-error-format-arguments condition)) + (format stream "~@" + (package-name (package-error-package condition))))))) + ;; no :default-initargs -- reference-stuff provided by the + ;; signalling form in target-package.lisp + #!+sb-doc + (:documentation + "Subtype of CL:PACKAGE-ERROR. A subtype of this error is signalled +when a package-lock is violated.")) + +(define-condition package-locked-error (package-lock-violation) () + #!+sb-doc + (:documentation + "Subtype of SB-EXT:PACKAGE-LOCK-VIOLATION. An error of this type is +signalled when an operation on a package violates a package lock.")) + +(define-condition symbol-package-locked-error (package-lock-violation) + ((symbol :initarg :symbol :reader package-locked-error-symbol)) + #!+sb-doc + (:documentation + "Subtype of SB-EXT:PACKAGE-LOCK-VIOLATION. An error of this type is +signalled when an operation on a symbol violates a package lock. The +symbol that caused the violation is accessed by the function +SB-EXT:PACKAGE-LOCKED-ERROR-SYMBOL.")) + +) ; progn + +(define-condition undefined-alien-error (error) ()) + +(define-condition undefined-alien-variable-error (undefined-alien-error) () + (:report + (lambda (condition stream) + (declare (ignore condition)) + (format stream "Attempt to access an undefined alien variable.")))) + +(define-condition undefined-alien-function-error (undefined-alien-error) () + (:report + (lambda (condition stream) + (declare (ignore condition)) + (format stream "Attempt to call an undefined alien function.")))) + + ;;;; various other (not specified by ANSI) CONDITIONs ;;;; ;;;; These might logically belong in other files; they're here, after ;;;; setup of CONDITION machinery, only because that makes it easier to ;;;; get cold init to work. +;;; OAOOM warning: see cross-condition.lisp +(define-condition encapsulated-condition (condition) + ((condition :initarg :condition :reader encapsulated-condition))) + (define-condition values-type-error (type-error) () (:report @@ -748,7 +1033,7 @@ "The index ~S is too large." (type-error-datum condition))))) -(define-condition bounding-indices-bad-error (type-error) +(define-condition bounding-indices-bad-error (reference-condition type-error) ((object :reader bounding-indices-bad-object :initarg :object)) (:report (lambda (condition stream) @@ -759,20 +1044,31 @@ (etypecase object (sequence (format stream - "The bounding indices ~S and ~S are bad for a sequence of length ~S." + "The bounding indices ~S and ~S are bad ~ + for a sequence of length ~S." start end (length object))) (array ;; from WITH-ARRAY-DATA (format stream - "The START and END parameters ~S and ~S are bad for an array of total size ~S." - start end (array-total-size object)))))))) - -(define-condition nil-array-accessed-error (type-error) + "The START and END parameters ~S and ~S are ~ + bad for an array of total size ~S." + start end (array-total-size object))))))) + (:default-initargs + :references + (list '(:ansi-cl :glossary "bounding index designator") + '(:ansi-cl :issue "SUBSEQ-OUT-OF-BOUNDS:IS-AN-ERROR")))) + +(define-condition nil-array-accessed-error (reference-condition type-error) () (:report (lambda (condition stream) + (declare (ignore condition)) (format stream "An attempt to access an array of element-type ~ - NIL was made. Congratulations!")))) + NIL was made. Congratulations!"))) + (:default-initargs + :references (list '(:ansi-cl :function sb!xc:upgraded-array-element-type) + '(:ansi-cl :section (15 1 2 1)) + '(:ansi-cl :section (15 1 2 2))))) (define-condition io-timeout (stream-error) ((direction :reader io-timeout-direction :initarg :direction)) @@ -817,87 +1113,77 @@ (lambda (condition stream) (let ((error-stream (stream-error-stream condition))) (format stream "READER-ERROR ~@[at ~W ~]on ~S:~%~?~%Original error: ~A" - (file-position error-stream) error-stream + (file-position-or-nil-for-error error-stream) error-stream (reader-error-format-control condition) (reader-error-format-arguments condition) (reader-impossible-number-error-error condition)))))) -(define-condition sb!ext::timeout (serious-condition) ()) +(define-condition timeout (serious-condition) ()) -(define-condition defconstant-uneql (error) - ((name :initarg :name :reader defconstant-uneql-name) - (old-value :initarg :old-value :reader defconstant-uneql-old-value) - (new-value :initarg :new-value :reader defconstant-uneql-new-value)) - (:report - (lambda (condition stream) - (format stream - "~@" - (defconstant-uneql-name condition) - (defconstant-uneql-old-value condition) - (defconstant-uneql-new-value condition))))) - -;;;; special SBCL extension conditions +(define-condition declaration-type-conflict-error (reference-condition + simple-error) + () + (:default-initargs + :format-control "symbol ~S cannot be both the name of a type and the name of a declaration" + :references (list '(:ansi-cl :section (3 8 21))))) -;;; an error apparently caused by a bug in SBCL itself -;;; -;;; Note that we don't make any serious effort to use this condition -;;; for *all* errors in SBCL itself. E.g. type errors and array -;;; indexing errors can occur in functions called from SBCL code, and -;;; will just end up as ordinary TYPE-ERROR or invalid index error, -;;; because the signalling code has no good way to know that the -;;; underlying problem is a bug in SBCL. But in the fairly common case -;;; that the signalling code does know that it's found a bug in SBCL, -;;; this condition is appropriate, reusing boilerplate and helping -;;; users to recognize it as an SBCL bug. -(define-condition bug (simple-error) +;;; Single stepping conditions + +(define-condition step-condition () + ((form :initarg :form :reader step-condition-form)) + #!+sb-doc + (:documentation "Common base class of single-stepping conditions. +STEP-CONDITION-FORM holds a string representation of the form being +stepped.")) + +#!+sb-doc +(setf (fdocumentation 'step-condition-form 'function) + "Form associated with the STEP-CONDITION.") + +(define-condition step-form-condition (step-condition) + ((source-path :initarg :source-path :reader step-condition-source-path) + (pathname :initarg :pathname :reader step-condition-pathname)) + #!+sb-doc + (:documentation "Condition signalled by code compiled with +single-stepping information when about to execute a form. +STEP-CONDITION-FORM holds the form, STEP-CONDITION-PATHNAME holds the +pathname of the original file or NIL, and STEP-CONDITION-SOURCE-PATH +holds the source-path to the original form within that file or NIL. +Associated with this condition are always the restarts STEP-INTO, +STEP-NEXT, and STEP-CONTINUE.")) + +#!+sb-doc +(setf (fdocumentation 'step-condition-source-path 'function) + "Source-path of the original form associated with the +STEP-FORM-CONDITION or NIL." + (fdocumentation 'step-condition-pathname 'function) + "Pathname of the original source-file associated with the +STEP-FORM-CONDITION or NIL.") + +(define-condition step-result-condition (step-condition) + ((result :initarg :result :reader step-condition-result))) + +#!+sb-doc +(setf (fdocumentation 'step-condition-result 'function) + "Return values associated with STEP-VALUES-CONDITION as a list, +or the variable value associated with STEP-VARIABLE-CONDITION.") + +(define-condition step-values-condition (step-result-condition) () - (:report - (lambda (condition stream) - (format stream - "~@< ~? ~:@_~?~:>" - (simple-condition-format-control condition) - (simple-condition-format-arguments condition) - "~@.~:@>" - '((fmakunbound 'compile)))))) -(defun bug (format-control &rest format-arguments) - (error 'bug - :format-control format-control - :format-arguments format-arguments)) + #!+sb-doc + (:documentation "Condition signalled by code compiled with +single-stepping information after executing a form. +STEP-CONDITION-FORM holds the form, and STEP-CONDITION-RESULT holds +the values returned by the form as a list. No associated restarts.")) + +(define-condition step-variable-condition (step-result-condition) + () + #!+sb-doc + (:documentation "Condition signalled by code compiled with +single-stepping information when referencing a variable. +STEP-CONDITION-FORM hold the symbol, and STEP-CONDITION-RESULT holds +the value of the variable. No associated restarts.")) -;;; a condition for use in stubs for operations which aren't supported -;;; on some platforms -;;; -;;; E.g. in sbcl-0.7.0.5, it might be appropriate to do something like -;;; #-(or freebsd linux) -;;; (defun load-foreign (&rest rest) -;;; (error 'unsupported-operator :name 'load-foreign)) -;;; #+(or freebsd linux) -;;; (defun load-foreign ... actual definition ...) -;;; By signalling a standard condition in this case, we make it -;;; possible for test code to distinguish between (1) intentionally -;;; unimplemented and (2) unintentionally just screwed up somehow. -;;; (Before this condition was defined, test code tried to deal with -;;; this by checking for FBOUNDP, but that didn't work reliably. In -;;; sbcl-0.7.0, a a package screwup left the definition of -;;; LOAD-FOREIGN in the wrong package, so it was unFBOUNDP even on -;;; architectures where it was supposed to be supported, and the -;;; regression tests cheerfully passed because they assumed that -;;; unFBOUNDPness meant they were running on an system which didn't -;;; support the extension.) -(define-condition unsupported-operator (cell-error) () - (:report - (lambda (condition stream) - (format stream - "unsupported on this platform (OS, CPU, whatever): ~S" - (cell-error-name condition))))) ;;;; restart definitions @@ -939,5 +1225,26 @@ "Transfer control and VALUE to a restart named USE-VALUE, or return NIL if none exists.")) +;;; single-stepping restarts + +(macrolet ((def (name doc) + #!-sb-doc (declare (ignore doc)) + `(defun ,name (condition) + #!+sb-doc ,doc + (invoke-restart (find-restart-or-control-error ',name condition))))) + (def step-continue + "Transfers control to the STEP-CONTINUE restart associated with +the condition, continuing execution without stepping. Signals a +CONTROL-ERROR if the restart does not exist.") + (def step-next + "Transfers control to the STEP-NEXT restart associated with the +condition, executing the current form without stepping and continuing +stepping with the next form. Signals CONTROL-ERROR is the restart does +not exists.") + (def step-into + "Transfers control to the STEP-INTO restart associated with the +condition, stepping into the current form. Signals a CONTROL-ERROR is +the restart does not exist.")) + (/show0 "condition.lisp end of file")