0.8.11.2:
[sbcl.git] / src / code / condition.lisp
index 5cdbc1a..f8e70f3 100644 (file)
@@ -72,7 +72,9 @@
   ;; allocation of this slot, or NIL until defaulted
   (allocation nil :type (member :instance :class nil))
   ;; If ALLOCATION is :CLASS, this is a cons whose car holds the value.
-  (cell nil :type (or cons null)))
+  (cell nil :type (or cons null))
+  ;; slot documentation
+  (documentation nil :type (or string null)))
 
 ;;; KLUDGE: It's not clear to me why CONDITION-CLASS has itself listed
 ;;; in its CPL, while other classes derived from CONDITION-CLASS don't
 ;;;; 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
                 (res (copy-structure sslot)))))))
     (res)))
 
-(defun %define-condition (name slots documentation report default-initargs)
+;;; Early definitions of slot accessor creators.
+;;;
+;;; Slot accessors must be generic functions, but ANSI does not seem
+;;; to specify any of them, and we cannot support it before end of
+;;; warm init. So we use ordinary functions inside SBCL, and switch to
+;;; GFs only at the end of building.
+(declaim (notinline install-condition-slot-reader
+                    install-condition-slot-writer))
+(defun install-condition-slot-reader (name condition slot-name)
+  (declare (ignore condition))
+  (setf (fdefinition name)
+        (lambda (condition)
+          (condition-reader-function condition slot-name))))
+(defun install-condition-slot-writer (name condition slot-name)
+  (declare (ignore condition))
+  (setf (fdefinition name)
+        (lambda (new-value condition)
+          (condition-writer-function condition new-value slot-name))))
+
+(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)
     (dolist (slot slots)
 
       ;; Set up reader and writer functions.
-      (let ((name (condition-slot-name slot)))
+      (let ((slot-name (condition-slot-name slot)))
        (dolist (reader (condition-slot-readers slot))
-         (setf (fdefinition reader)
-               (lambda (condition)
-                 (condition-reader-function condition name))))
+          (install-condition-slot-reader reader name slot-name))
        (dolist (writer (condition-slot-writers slot))
-         (setf (fdefinition writer)
-               (lambda (new-value condition)
-                 (condition-writer-function condition new-value name))))))
+         (install-condition-slot-writer writer name slot-name))))
 
     ;; Compute effective slots and set up the class and hairy slots
     ;; (subsets of the effective slots.)
               (slot-name (first spec))
               (allocation :instance)
               (initform-p nil)
+              documentation
               initform)
          (collect ((initargs)
                    (readers)
                  (:initarg (initargs arg))
                  (:allocation
                   (setq allocation arg))
+                 (:documentation
+                  (when documentation
+                    (error "more than one :DOCUMENTATION in ~S" spec))
+                  (unless (stringp arg)
+                    (error "slot :DOCUMENTATION argument is not a string: ~S"
+                           arg))
+                  (setq documentation arg))
                  (:type)
                  (t
                   (error "unknown slot option:~%  ~S" (first options))))))
                     :readers ',(readers)
                     :writers ',(writers)
                     :initform-p ',initform-p
+                    :documentation ',documentation
                     :initform
                     ,(if (constantp initform)
                          `',(eval initform)
           (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
 
 ;;; methods)
 (defun describe-condition (condition stream)
   (format stream
-         "~@<~S ~_is a ~S. ~_Its slot values are ~_~S.~:>"
+         "~&~@<~S ~_is a ~S. ~_Its slot values are ~_~S.~:>~%"
          condition
          (type-of condition)
          (concatenate 'list
 
 (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) ())
     :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
 ;;;; various other (not specified by ANSI) CONDITIONs
 ;;;;
 ;;;; setup of CONDITION machinery, only because that makes it easier to
 ;;;; get cold init to work.
 
+(define-condition simple-style-warning (simple-condition style-warning) ())
+
+(define-condition values-type-error (type-error)
+  ()
+  (:report
+   (lambda (condition stream)
+     (format stream
+            "~@<The values set ~2I~:_[~{~S~^ ~}] ~I~_is not of type ~2I~_~S.~:>"
+            (type-error-datum condition)
+            (type-error-expected-type condition)))))
+
 ;;; KLUDGE: a condition for floating point errors when we can't or
 ;;; won't figure out what type they are. (In FreeBSD and OpenBSD we
 ;;; don't know how, at least as of sbcl-0.6.7; in Linux we probably
 (define-condition nil-array-accessed-error (type-error)
   ()
   (:report (lambda (condition stream)
+            (declare (ignore condition))
             (format stream
                     "An attempt to access an array of element-type ~
                       NIL was made.  Congratulations!"))))
               (reader-error-format-arguments condition)
               (reader-impossible-number-error-error condition))))))
 
-(define-condition sb!ext::timeout (serious-condition) ())
-
-
+(define-condition timeout (serious-condition) ())
 \f
 ;;;; special SBCL extension conditions
 
               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
             "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 ~S" 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 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
 ;;;; restart definitions
 
 (define-condition abort-failure (control-error) ()
   #!+sb-doc
   "Transfer control to a restart named ABORT, signalling a CONTROL-ERROR if
    none exists."
-  (invoke-restart (find-restart 'abort condition))
+  (invoke-restart (find-restart-or-control-error 'abort condition))
   ;; ABORT signals an error in case there was a restart named ABORT
   ;; that did not transfer control dynamically. This could happen with
   ;; RESTART-BIND.
   #!+sb-doc
   "Transfer control to a restart named MUFFLE-WARNING, signalling a
    CONTROL-ERROR if none exists."
-  (invoke-restart (find-restart 'muffle-warning condition)))
+  (invoke-restart (find-restart-or-control-error 'muffle-warning condition)))
 
 (macrolet ((define-nil-returning-restart (name args doc)
             #!-sb-doc (declare (ignore doc))