0.8.12.4:
[sbcl.git] / src / code / condition.lisp
index 4e686ef..5345544 100644 (file)
 ;;;; DEFINE-CONDITION
 
 (eval-when (:compile-toplevel :load-toplevel :execute)
-(defun %compiler-define-condition (name direct-supers layout)
+(defun %compiler-define-condition (name direct-supers layout
+                                  all-readers all-writers)
+  (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
          (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
         (lambda (new-value condition)
           (condition-writer-function condition new-value slot-name))))
 
-(defun %define-condition (name slots documentation report default-initargs)
+(defun %define-condition (name parent-types layout slots documentation
+                         report default-initargs all-readers all-writers)
+  (%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)
           (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)))))))
 \f
 ;;;; DESCRIBE on CONDITIONs
 
 
 (define-condition simple-condition ()
   ((format-control :reader simple-condition-format-control
-                  :initarg :format-control)
+                  :initarg :format-control
+                   :type format-control)
    (format-arguments :reader simple-condition-format-arguments
                     :initarg :format-arguments
-                    :initform '()))
+                    :initform '()
+                     :type list))
   (:report simple-condition-printer))
 
 (define-condition simple-warning (simple-condition warning) ())
 
 (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)
     :initform '()))
   (:report
    (lambda (condition stream)
-     (let ((error-stream (stream-error-stream condition)))
-       (format stream "READER-ERROR ~@[at ~W ~]on ~S:~%~?"
-              (file-position error-stream) error-stream
-              (reader-error-format-control condition)
-              (reader-error-format-arguments condition))))))
+     (let* ((error-stream (stream-error-stream condition))
+           (pos (file-position 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))))
+            (when (= pos (read-sequence string error-stream))
+              (setq lineno (1+ (count #\Newline string))
+                    colno (- pos
+                             (or (position #\Newline string :from-end t) -1)
+                             1))))
+          (file-position error-stream pos))
+        (format stream
+                "READER-ERROR ~@[at ~W ~]~
+                  ~@[(line ~W~]~@[, column ~W) ~]~
+                  on ~S:~%~?"
+                pos lineno colno error-stream
+                (reader-error-format-control condition)
+                (reader-error-format-arguments condition)))))))
+\f
+;;;; 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)
+            "~@<This is probably a bug in SBCL itself. (Alternatively, ~
+              SBCL might have been corrupted by bad user code, e.g. by an ~
+              undefined Lisp operation like ~S, or by stray pointers from ~
+              alien code or from unsafe Lisp code; or there might be a bug ~
+              in the OS or hardware that SBCL is running on.) If it seems to ~
+              be a bug in SBCL itself, the maintainers would like to know ~
+              about it. Bug reports are welcome on the SBCL ~
+              mailing lists, which you can find at ~
+              <http://sbcl.sourceforge.net/>.~:@>"
+            '((fmakunbound 'compile))))))
+
+;;; 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)))))
+\f
+;;; (: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)
+    (: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)))))
+    ;; FIXME: other documents (e.g. AMOP, 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 *print-condition-references*
+      (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 for ~S found in ~
+                        one file.~@:>"
+                    (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
+            "~@<The constant ~S is being redefined (from ~S to ~S)~@:>"
+            (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)
+  ())
 \f
 ;;;; various other (not specified by ANSI) CONDITIONs
 ;;;;
             "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)
        (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))
               (reader-error-format-arguments condition)
               (reader-impossible-number-error-error condition))))))
 
-(define-condition sb!ext::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
-            "~@<The constant ~S is being redefined (from ~S to ~S)~@:>"
-            (defconstant-uneql-name condition)
-            (defconstant-uneql-old-value condition)
-            (defconstant-uneql-new-value condition)))))
-\f
-;;;; 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)
-            "~@<This is probably a bug in SBCL itself. (Alternatively, ~
-              SBCL might have been corrupted by bad user code, e.g. by an ~
-              undefined Lisp operation like ~S, or by stray pointers from ~
-              alien code or from unsafe Lisp code; or there might be a bug ~
-              in the OS or hardware that SBCL is running on.) If it seems to ~
-              be a bug in SBCL itself, the maintainers would like to know ~
-              about it. Bug reports are welcome on the SBCL ~
-              mailing lists, which you can find at ~
-              <http://sbcl.sourceforge.net/>.~:@>"
-            '((fmakunbound 'compile))))))
-(defun bug (format-control &rest format-arguments)
-  (error 'bug
-        :format-control format-control
-        :format-arguments format-arguments))
-
-;;; 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)))))
+(define-condition timeout (serious-condition) ())
 \f
 ;;;; restart definitions