teach NODE-CONSERVATIVE-TYPE about union types
[sbcl.git] / src / compiler / array-tran.lisp
index a3cea57..baf1b98 100644 (file)
@@ -73,7 +73,7 @@
                  (apply #'type-intersection element-supertypes)))))
     (union-type
      (let ((union-types (union-type-types type))
-           (element-type *empty-type*)
+           (element-type nil)
            (element-supertypes nil))
        (dolist (union-type union-types)
          (multiple-value-bind (cur-type cur-supertype)
@@ -81,7 +81,7 @@
            (cond
              ((eq element-type *wild-type*)
               nil)
-             ((eq element-type *empty-type*)
+             ((eq element-type nil)
               (setf element-type cur-type))
              ((or (eq cur-type *wild-type*)
                   ;; If each of the two following tests fail, it is not
        (values element-type
                (when (eq *wild-type* element-type)
                  (apply #'type-union element-supertypes)))))
+    (member-type
+     ;; Convert member-type to an union-type.
+     (array-type-upgraded-element-type
+      (apply #'type-union (mapcar #'ctype-of (member-type-members type)))))
     (t
      ;; KLUDGE: there is no good answer here, but at least
      ;; *wild-type* won't cause HAIRY-DATA-VECTOR-{REF,SET} to be
        (lexenv-policy (node-lexenv (lvar-dest new-value))))))
   (lvar-type new-value))
 
-(defun assert-array-complex (array)
-  (assert-lvar-type
-   array
-   (make-array-type :complexp t
-                    :element-type *wild-type*)
-   (lexenv-policy (node-lexenv (lvar-dest array))))
-  nil)
-
 ;;; Return true if ARG is NIL, or is a constant-lvar whose
 ;;; value is NIL, false otherwise.
 (defun unsupplied-or-nil (arg)
   (or (not arg)
       (and (constant-lvar-p arg)
            (not (lvar-value arg)))))
+
+(defun supplied-and-true (arg)
+  (and arg
+       (constant-lvar-p arg)
+       (lvar-value arg)
+       t))
 \f
 ;;;; DERIVE-TYPE optimizers
 
     (block nil
       (let ((dimensions (array-type-dimensions-or-give-up
                          (lvar-conservative-type array))))
+        ;; Might be *. (Note: currently this is never true, because the type
+        ;; derivation infers the rank from the call to ARRAY-IN-BOUNDS-P, but
+        ;; let's keep this future proof.)
+        (when (eq '* dimensions)
+          (give-up-ir1-transform "array bounds unknown"))
         ;; shortcut for zero dimensions
         (when (some (lambda (dim)
                       (and (bound-known-p dim) (zerop dim)))
         ;; we can already decide on the result of the optimization without
         ;; even taking a look at the dimensions.
         (flet ((subscript-bounds (subscript)
-                 (let* ((type (lvar-type subscript))
-                        (low (numeric-type-low type))
-                        (high (numeric-type-high type)))
+                 (let* ((type1 (lvar-type subscript))
+                        (type2 (if (csubtypep type1 (specifier-type 'integer))
+                                   (weaken-integer-type type1 :range-only t)
+                                   (give-up)))
+                        (low (if (integer-type-p type2)
+                                 (numeric-type-low type2)
+                                 (give-up)))
+                        (high (numeric-type-high type2)))
                    (cond
                      ((and (or (not (bound-known-p low)) (minusp low))
                            (or (not (bound-known-p high)) (not (minusp high))))
 (defoptimizer (make-array derive-type)
               ((dims &key initial-element element-type initial-contents
                 adjustable fill-pointer displaced-index-offset displaced-to))
-  (let ((simple (and (unsupplied-or-nil adjustable)
-                     (unsupplied-or-nil displaced-to)
-                     (unsupplied-or-nil fill-pointer))))
-    (or (careful-specifier-type
-         `(,(if simple 'simple-array 'array)
-            ,(cond ((not element-type) t)
-                   ((constant-lvar-p element-type)
-                    (let ((ctype (careful-specifier-type
-                                  (lvar-value element-type))))
-                      (cond
-                        ((or (null ctype) (unknown-type-p ctype)) '*)
-                        (t (sb!xc:upgraded-array-element-type
-                            (lvar-value element-type))))))
-                   (t
-                    '*))
-            ,(cond ((constant-lvar-p dims)
-                    (let* ((val (lvar-value dims))
-                           (cdims (if (listp val) val (list val))))
-                      (if simple
-                          cdims
-                          (length cdims))))
-                   ((csubtypep (lvar-type dims)
-                               (specifier-type 'integer))
-                    '(*))
-                   (t
-                    '*))))
-        (specifier-type 'array))))
-
-;;; Complex array operations should assert that their array argument
-;;; is complex.  In SBCL, vectors with fill-pointers are complex.
-(defoptimizer (fill-pointer derive-type) ((vector))
-  (assert-array-complex vector))
-(defoptimizer (%set-fill-pointer derive-type) ((vector index))
-  (declare (ignorable index))
-  (assert-array-complex vector))
-
-(defoptimizer (vector-push derive-type) ((object vector))
-  (declare (ignorable object))
-  (assert-array-complex vector))
-(defoptimizer (vector-push-extend derive-type)
-    ((object vector &optional index))
-  (declare (ignorable object index))
-  (assert-array-complex vector))
-(defoptimizer (vector-pop derive-type) ((vector))
-  (assert-array-complex vector))
+  (let* ((simple (and (unsupplied-or-nil adjustable)
+                      (unsupplied-or-nil displaced-to)
+                      (unsupplied-or-nil fill-pointer)))
+         (spec
+          (or `(,(if simple 'simple-array 'array)
+                 ,(cond ((not element-type) t)
+                        ((constant-lvar-p element-type)
+                         (let ((ctype (careful-specifier-type
+                                       (lvar-value element-type))))
+                           (cond
+                             ((or (null ctype) (unknown-type-p ctype)) '*)
+                             (t (sb!xc:upgraded-array-element-type
+                                 (lvar-value element-type))))))
+                        (t
+                         '*))
+                 ,(cond ((constant-lvar-p dims)
+                         (let* ((val (lvar-value dims))
+                                (cdims (if (listp val) val (list val))))
+                           (if simple
+                               cdims
+                               (length cdims))))
+                        ((csubtypep (lvar-type dims)
+                                    (specifier-type 'integer))
+                         '(*))
+                        (t
+                         '*)))
+              'array)))
+    (if (and (not simple)
+             (or (supplied-and-true adjustable)
+                 (supplied-and-true displaced-to)
+                 (supplied-and-true fill-pointer)))
+        (careful-specifier-type `(and ,spec (not simple-array)))
+        (careful-specifier-type spec))))
 \f
 ;;;; constructors
 
 ;;; can pick them apart in the DEFTRANSFORMS, and transform '(3) style
 ;;; dimensions to integer args directly.
 (define-source-transform make-array (dimensions &rest keyargs &environment env)
-  (if (and (fun-lexically-notinline-p 'list)
-           (fun-lexically-notinline-p 'vector))
+  (if (or (and (fun-lexically-notinline-p 'list)
+               (fun-lexically-notinline-p 'vector))
+          (oddp (length keyargs)))
       (values nil t)
       (multiple-value-bind (new-dimensions rank)
           (flet ((constant-dims (dimensions)
              `(deftransform ,name ((array index ,@extra))
                 (let* ((type (lvar-type array))
                        (element-type (array-type-upgraded-element-type type))
-                       (declared-type (array-type-declared-element-type type)))
+                       (declared-type (type-specifier
+                                       (array-type-declared-element-type type))))
                   ;; If an element type has been declared, we want to
                   ;; use that information it for type checking (even
                   ;; if the access can't be optimized due to the array