-tREPORTING BUGS
+REPORTING BUGS
 
 Bugs can be reported on the help mailing list
   sbcl-help@lists.sourceforge.net
   then executing
     (FOO 1.5)
   will cause the INTEGERP case to be selected, giving bogus output a la
-    exactly 1.33..
+    exactly 2.5
+  (or (FOO 1000.5), "exactly 1001.5")
   This violates the "declarations are assertions" principle.
   According to the ANSI spec, in the section "System Class FUNCTION",
   this is a case of "lying to the compiler", but the lying is done
      lists and &KEY arguments) do not signal errors when they should.
 
 192: "Python treats free type declarations as promises."
-  a. original report by Alexey Dejneka (on sbcl-devel 2002-08-26):
-       (declaim (optimize (speed 0) (safety 3)))
-       (defun f (x)
-         (declare (real x))
-         (+ x
-            (locally (declare (single-float x))
-            (sin x))))
-     Now (F NIL) correctly gives a type error, but (F 100) gives
-     a segmentation violation.
-  b. same fundamental problem in a different way, easy to stumble
-     across if you mistype and declare the wrong index in
+  b. What seemed like the same fundamental problem as bug 192a, but
+     was not fixed by the same (APD "more strict type checking
+     sbcl-devel 2002-08-97) patch:
      (DOTIMES (I ...) (DOTIMES (J ...) (DECLARE ...) ...)):
        (declaim (optimize (speed 1) (safety 3)))
        (defun trust-assertion (i)
   bad argument value is).
 
 194: "no error from (THE REAL '(1 2 3)) in some cases"
-  (Actually this entry is probably two separate bugs, as
-  Alexey Dejneka commented on sbcl-devel 2002-09-03:)
+  fixed parts:
+    a. In sbcl-0.7.7.9, 
+         (multiple-value-prog1 (progn (the real '(1 2 3))))
+       returns (1 2 3) instead of signalling an error. This was fixed by 
+       APD's "more strict type checking patch", but although the fixed
+       code (in sbcl-0.7.7.19) works (signals TYPE-ERROR) interactively,
+       it's difficult to write a regression test for it, because 
+       (IGNORE-ERRORS (MULTIPLE-VALUE-PROG1 (PROGN (THE REAL '(1 2 3)))))
+       still returns (1 2 3).
+  still-broken parts:  
+    b. (IGNORE-ERRORS (MULTIPLE-VALUE-PROG1 (PROGN (THE REAL '(1 2 3)))))    
+       returns (1 2 3). (As above, this shows up when writing regression
+       tests for fixed-ness of part a.)
+    c. Also in sbcl-0.7.7.9, (IGNORE-ERRORS (THE REAL '(1 2 3))) => (1 2 3).
+    d. At the REPL,
+         (null (ignore-errors
+           (let ((arg1 1)
+                 (arg2 (identity (the real #(1 2 3)))))
+             (if (< arg1 arg2) arg1 arg2))))
+           => T
+      but putting the same expression inside (DEFUN FOO () ...),
+      (FOO) => NIL.
+  notes:
+    * Actually this entry is probably multiple bugs, as
+      Alexey Dejneka commented on sbcl-devel 2002-09-03:)
        I don't think that placing these two bugs in one entry is
        a good idea: they have different explanations. The second
        (min 1 nil) is caused by flushing of unused code--IDENTITY
        for the result, it forgets about type assertion. The purpose
        of IDENTITY is to save the restricted continuation from
        inaccurate transformations.
-  In sbcl-0.7.7.9, 
-    (multiple-value-prog1 (progn (the real '(1 2 3))))
-  returns (1 2 3) instead of signalling an error. Also in sbcl-0.7.7.9,
-  a more complicated instance of this bug kept 
-  (IGNORE-ERRORS (MIN '(1 2 3))) from returning NIL as it should when
-  the MIN source transform expanded to (THE REAL '(1 2 3)), because
-  (IGNORE-ERRORS (THE REAL '(1 2 3))) returns (1 2 3).
-  Alexey Dejneka pointed out that
-  (IGNORE-ERRORS (IDENTITY (THE REAL '(1 2 3)))) works as it should.
-  (IGNORE-ERRORS (VALUES (THE REAL '(1 2 3)))) also works as it should.
-  Perhaps this is another case of VALUES type intersections behaving
-  in non-useful ways?
-    When I (WHN) tried to use the VALUES trick to work around this bug
-  in the MIN source transform, it didn't work for
-    (assert (null (ignore-errors (min 1 #(1 2 3)))))
-  Hand-expanding the source transform, I get
-    (assert (null (ignore-errors
-                   (let ((arg1 1)
-                         (arg2 (identity (the real #(1 2 3)))))
-                     (if (< arg1 arg2) arg1 arg2))))) 
-  which fails (i.e. the assertion fails, because the IGNORE-ERRORS
-  doesn't report MIN signalling a type error). At the REPL
-    (null (ignore-errors
-           (let ((arg1 1)
-                 (arg2 (identity (the real #(1 2 3)))))
-             (if (< arg1 arg2) arg1 arg2))))
-    => T
-  but when this expression is used as the body of (DEFUN FOO () ...)
-  then (FOO)=>NIL.
+    * Alexey Dejneka pointed out that
+       (IGNORE-ERRORS (IDENTITY (THE REAL '(1 2 3))))
+      works as it should. Also
+       (IGNORE-ERRORS (VALUES (THE REAL '(1 2 3))))
+      works as it should. Perhaps this is another case of VALUES type
+      intersections behaving in non-useful ways?
 
 195: "confusing reporting of not-a-REAL TYPE-ERRORs from THE REAL"
   In sbcl-0.7.7.10, (THE REAL #(1 2 3)) signals a type error which
 
     found).
   * fixed bug 174: FORMAT's error message is slightly clearer when a
     non-printing character is used in a format directive.
+  * fixed several bugs in compiler checking of type declarations, i.e.
+    violations of the Python "declarations are assertions" principle
+    (thanks to Alexey Dejneka)
 
 planned incompatible changes in 0.7.x:
 * When the profiling interface settles down, maybe in 0.7.x, maybe
 
 ;;; We make this work by getting USE-CONTINUATION to do the unioning
 ;;; across COND branches. We can't do it here, since we don't know how
 ;;; many branches there are going to be.
-(defun ir1ize-the-or-values (type cont lexenv name)
+(defun ir1ize-the-or-values (type cont lexenv place)
   (declare (type continuation cont) (type lexenv lexenv))
-  (let* ((ctype (values-specifier-type type))
+  (let* ((ctype (if (typep type 'ctype) type (values-specifier-type type)))
         (old-type (or (lexenv-find cont type-restrictions)
                       *wild-type*))
         (intersects (values-types-equal-or-intersect old-type ctype))
               (not (policy *lexenv*
                            (= inhibit-warnings 3)))) ;FIXME: really OK to suppress?
       (compiler-warn
-       "The type ~S in ~S declaration conflicts with an ~
+       "The type ~S ~A conflicts with an ~
         enclosing assertion:~%   ~S"
        (type-specifier ctype)
-       name
+       place
        (type-specifier old-type)))
     (make-lexenv :type-restrictions `((,cont . ,new))
                 :default lexenv)))
 ;;; this didn't seem to expand into an assertion, at least for ALIEN
 ;;; values. Check that SBCL doesn't have this problem.
 (def-ir1-translator the ((type value) start cont)
-  (let ((*lexenv* (ir1ize-the-or-values type cont *lexenv* 'the)))
+  (with-continuation-type-assertion (cont (values-specifier-type type)
+                                          "in THE declaration")
     (ir1-convert start cont value)))
 
 ;;; This is like the THE special form, except that it believes
     (continuation-starts-block dummy-start)
     (ir1-convert start dummy-start result)
 
-    (substitute-continuation-uses cont dummy-start)
+    (with-continuation-type-assertion
+        (cont (continuation-asserted-type dummy-start)
+              "of the first form")
+      (substitute-continuation-uses cont dummy-start))
 
     (continuation-starts-block dummy-result)
     (ir1-convert-progn-body dummy-start dummy-result forms)
 
 ;;; functional instead.
 (defun reference-leaf (start cont leaf)
   (declare (type continuation start cont) (type leaf leaf))
-  (let* ((leaf (or (and (defined-fun-p leaf)
-                       (not (eq (defined-fun-inlinep leaf)
-                                :notinline))
-                       (let ((functional (defined-fun-functional leaf)))
-                         (when (and functional
-                                    (not (functional-kind functional)))
-                           (maybe-reanalyze-functional functional))))
-                  leaf))
-        (res (make-ref (or (lexenv-find leaf type-restrictions)
-                           (leaf-type leaf))
-                       leaf)))
-    (push res (leaf-refs leaf))
-    (setf (leaf-ever-used leaf) t)
-    (link-node-to-previous-continuation res start)
-    (use-continuation res cont)))
+  (with-continuation-type-assertion
+      (cont (or (lexenv-find leaf type-restrictions) *wild-type*)
+            "in DECLARE")
+    (let* ((leaf (or (and (defined-fun-p leaf)
+                          (not (eq (defined-fun-inlinep leaf)
+                                   :notinline))
+                          (let ((functional (defined-fun-functional leaf)))
+                            (when (and functional
+                                       (not (functional-kind functional)))
+                              (maybe-reanalyze-functional functional))))
+                     leaf))
+           (res (make-ref (leaf-type leaf)
+                          leaf)))
+      (push res (leaf-refs leaf))
+      (setf (leaf-ever-used leaf) t)
+      (link-node-to-previous-continuation res start)
+      (use-continuation res cont))))
 
 ;;; Convert a reference to a symbolic constant or variable. If the
 ;;; symbol is entered in the LEXENV-VARS we use that definition,
                                       `(values ,@types))
                                   cont
                                   res
-                                  'values))))
+                                  "in VALUES declaration"))))
       (dynamic-extent
        (when (policy *lexenv* (> speed inhibit-warnings))
         (compiler-note
 
     `(if ,n-res
         (values (cdr ,n-res) t)
         (values nil nil))))
+
+;;;
+(defmacro with-continuation-type-assertion ((cont ctype context) &body body)
+  `(let ((*lexenv* (ir1ize-the-or-values ,ctype ,cont *lexenv* ,context)))
+     ,@body))
 \f
 ;;;; the EVENT statistics/trace utility
 
 
            ;; Uncomment and it works
            ))
     (eff)))
+
+;;; bug 192a, fixed by APD "more strict type checking" patch
+;;; (sbcl-devel 2002-08-07)
+(defun bug192a (x)
+  (declare (optimize (speed 0) (safety 3)))
+  ;; Even with bug 192a, this declaration was checked as an assertion.
+  (declare (real x))
+  (+ x
+     (locally
+       ;; Because of bug 192a, this declaration was trusted without checking.
+       (declare (single-float x))
+       (sin x))))
+(assert (null (ignore-errors (bug192a nil))))
+(multiple-value-bind (result error) (ignore-errors (bug192a 100))
+  (assert (null result))
+  (assert (equal (type-error-expected-type error) 'single-float)))
+
+;;; bug 194, fixed in part by APD "more strict type checking" patch
+;;; (sbcl-devel 2002-08-07)
+(progn
+  #+nil ; FIXME: still broken in 0.7.7.19 (after patch)
+  (multiple-value-bind (result error)
+      (ignore-errors (multiple-value-prog1 (progn (the real '(1 2 3)))))
+    (assert (null result))
+    (assert (typep error 'type-error)))
+  #+nil ; FIXME: still broken in 0.7.7.19 (after patch)
+  (multiple-value-bind (result error)
+      (ignore-errors (the real '(1 2 3)))
+    (assert (null result))
+    (assert (typep error 'type-error))))
 \f
 ;;; BUG 48a. and b. (symbol-macrolet handling), fixed by Eric Marsden
 ;;; and Raymond Toy for CMUCL, fix ported for sbcl-0.7.6.18.
     (compile nil '(lambda () (symbol-macrolet ((t nil)) t)))
   (assert failure-p)
   (assert (raises-error? (funcall function) program-error)))
-
 (multiple-value-bind (function warnings-p failure-p)
-    (compile nil '(lambda () (symbol-macrolet ((*standard-input* nil)) *standard-input*)))
+    (compile nil
+            '(lambda ()
+               (symbol-macrolet ((*standard-input* nil))
+                 *standard-input*)))
   (assert failure-p)
   (assert (raises-error? (funcall function) program-error)))
 #||
 
   (declare (type list keys))
   (loop
       for c in '#1=("Red" "Blue" . #1#)
-      for key in keys ))
+      for key in keys))
 
 ;;; sbcl-0.6.11.25 or so had DEF!STRUCT/MAKE-LOAD-FORM/HOST screwed up
 ;;; so that the compiler couldn't dump pathnames.
 
 ;;; for internal versions, especially for internal versions off the
 ;;; main CVS branch, it gets hairier, e.g. "0.pre7.14.flaky4.13".)
 
-"0.7.7.18"
+"0.7.7.19"