1.0.12.13: sequence optimizations: SUBSEQ, part 3
[sbcl.git] / src / code / array.lisp
index a3c6793..4268f55 100644 (file)
            (fixnum index))
   (%check-bound array bound index))
 
+(defun %with-array-data/fp (array start end)
+  (%with-array-data-macro array start end :check-bounds t :check-fill-pointer t))
+
 (defun %with-array-data (array start end)
-  (%with-array-data-macro array start end :fail-inline? t))
+  (%with-array-data-macro array start end :check-bounds t :check-fill-pointer nil))
 
 (defun %data-vector-and-index (array index)
   (if (array-header-p array)
           (%with-array-data array index nil)
         (values vector index))
       (values array index)))
-
-;;; It'd waste space to expand copies of error handling in every
-;;; inline %WITH-ARRAY-DATA, so we have them call this function
-;;; instead. This is just a wrapper which is known never to return.
-(defun failed-%with-array-data (array start end)
-  (declare (notinline %with-array-data))
-  (%with-array-data array start end)
-  (bug "called FAILED-%WITH-ARRAY-DATA with valid array parameters?"))
 \f
 ;;;; MAKE-ARRAY
 (eval-when (:compile-toplevel :execute)
     (declare (fixnum array-rank))
     (when (and displaced-index-offset (null displaced-to))
       (error "can't specify :DISPLACED-INDEX-OFFSET without :DISPLACED-TO"))
+    (when (and displaced-to
+               (arrayp displaced-to)
+               (not (equal (array-element-type displaced-to)
+                           (upgraded-array-element-type element-type))))
+      (error "Array element type of :DISPLACED-TO array does not match specified element type"))
     (if (and simple (= array-rank 1))
         ;; it's a (SIMPLE-ARRAY * (*))
         (multiple-value-bind (type n-bits)
@@ -306,49 +306,166 @@ of specialized arrays is supported."
            (fill-data-vector data dimensions initial-contents)))
     data))
 
-(defun fill-data-vector (vector dimensions initial-contents)
-  (let ((index 0))
-    (labels ((frob (axis dims contents)
-               (cond ((null dims)
-                      (setf (aref vector index) contents)
-                      (incf index))
-                     (t
-                      (unless (typep contents 'sequence)
-                        (error "malformed :INITIAL-CONTENTS: ~S is not a ~
-                                sequence, but ~W more layer~:P needed."
-                               contents
-                               (- (length dimensions) axis)))
-                      (unless (= (length contents) (car dims))
-                        (error "malformed :INITIAL-CONTENTS: Dimension of ~
-                                axis ~W is ~W, but ~S is ~W long."
-                               axis (car dims) contents (length contents)))
-                      (if (listp contents)
-                          (dolist (content contents)
-                            (frob (1+ axis) (cdr dims) content))
-                          (dotimes (i (length contents))
-                            (frob (1+ axis) (cdr dims) (aref contents i))))))))
-      (frob 0 dimensions initial-contents))))
-
 (defun vector (&rest objects)
   #!+sb-doc
   "Construct a SIMPLE-VECTOR from the given objects."
   (coerce (the list objects) 'simple-vector))
 \f
+
 ;;;; accessor/setter functions
-(defun hairy-data-vector-ref (array index)
-  (with-array-data ((vector array) (index index) (end))
-    (declare (ignore end))
-    (etypecase vector .
-               #.(map 'list
-                      (lambda (saetp)
-                        (let* ((type (sb!vm:saetp-specifier saetp))
-                               (atype `(simple-array ,type (*))))
-                          `(,atype
-                            (data-vector-ref (the ,atype vector) index))))
-                      (sort
-                       (copy-seq
-                        sb!vm:*specialized-array-element-type-properties*)
-                       #'> :key #'sb!vm:saetp-importance)))))
+
+;;; Dispatch to an optimized routine the data vector accessors for
+;;; each different specialized vector type. Do dispatching by looking
+;;; up the widetag in the array rather than with the typecases, which
+;;; as of 1.0.5 compiles to a naive sequence of linear TYPEPs. Also
+;;; provide separate versions where bounds checking has been moved
+;;; from the callee to the caller, since it's much cheaper to do once
+;;; the type information is available. Finally, for each of these
+;;; routines also provide a slow path, taken for arrays that are not
+;;; vectors or not simple.
+(macrolet ((def (name table-name)
+             `(progn
+                (defvar ,table-name)
+                (defmacro ,name (array-var)
+                 `(the function
+                    (let ((tag 0)
+                          (offset
+                           #.(ecase sb!c:*backend-byte-order*
+                               (:little-endian
+                                (- sb!vm:other-pointer-lowtag))
+                               (:big-endian
+                                (- (1- sb!vm:n-word-bytes) sb!vm:other-pointer-lowtag)))))
+                      ;; WIDETAG-OF needs extra code to handle LIST and
+                      ;; FUNCTION lowtags. We're only dispatching on
+                      ;; other pointers, so let's do the lowtag
+                      ;; extraction manually.
+                      (when (sb!vm::%other-pointer-p ,array-var)
+                        (setf tag
+                              (sb!sys:sap-ref-8 (int-sap (get-lisp-obj-address ,array-var))
+                                                offset)))
+                      ;; SYMBOL-GLOBAL-VALUE is a performance hack
+                      ;; for threaded builds.
+                      (svref (sb!vm::symbol-global-value ',',table-name) tag)))))))
+  (def !find-data-vector-setter *data-vector-setters*)
+  (def !find-data-vector-setter/check-bounds *data-vector-setters/check-bounds*)
+  (def !find-data-vector-reffer *data-vector-reffers*)
+  (def !find-data-vector-reffer/check-bounds *data-vector-reffers/check-bounds*))
+
+(macrolet ((%ref (accessor-getter extra-params)
+             `(funcall (,accessor-getter array) array index ,@extra-params))
+           (define (accessor-name slow-accessor-name accessor-getter
+                                  extra-params check-bounds)
+             `(progn
+                (defun ,accessor-name (array index ,@extra-params)
+                  (declare (optimize speed
+                                     ;; (SAFETY 0) is ok. All calls to
+                                     ;; these functions are generated by
+                                     ;; the compiler, so argument count
+                                     ;; checking isn't needed. Type checking
+                                     ;; is done implicitly via the widetag
+                                     ;; dispatch.
+                                     (safety 0)))
+                  (%ref ,accessor-getter ,extra-params))
+                (defun ,slow-accessor-name (array index ,@extra-params)
+                  (declare (optimize speed (safety 0)))
+                  (if (not (%array-displaced-p array))
+                      ;; The reasonably quick path of non-displaced complex
+                      ;; arrays.
+                      (let ((array (%array-data-vector array)))
+                        (%ref ,accessor-getter ,extra-params))
+                      ;; The real slow path.
+                      (with-array-data
+                          ((vector array)
+                           (index (locally
+                                      (declare (optimize (speed 1) (safety 1)))
+                                    (,@check-bounds index)))
+                           (end)
+                           :force-inline t)
+                        (declare (ignore end))
+                        (,accessor-name vector index ,@extra-params)))))))
+  (define hairy-data-vector-ref slow-hairy-data-vector-ref
+    !find-data-vector-reffer
+    nil (progn))
+  (define hairy-data-vector-set slow-hairy-data-vector-set
+    !find-data-vector-setter
+    (new-value) (progn))
+  (define hairy-data-vector-ref/check-bounds
+      slow-hairy-data-vector-ref/check-bounds
+    !find-data-vector-reffer/check-bounds
+    nil (%check-bound array (array-dimension array 0)))
+  (define hairy-data-vector-set/check-bounds
+      slow-hairy-data-vector-set/check-bounds
+    !find-data-vector-setter/check-bounds
+    (new-value) (%check-bound array (array-dimension array 0))))
+
+(defun hairy-ref-error (array index &optional new-value)
+  (declare (ignore index new-value))
+  (error 'type-error
+         :datum array
+         :expected-type 'vector))
+
+;;; Populate the dispatch tables.
+(macrolet ((define-reffer (saetp check-form)
+             (let* ((type (sb!vm:saetp-specifier saetp))
+                    (atype `(simple-array ,type (*))))
+               `(named-lambda optimized-data-vector-ref (vector index)
+                  (declare (optimize speed (safety 0)))
+                  (data-vector-ref (the ,atype vector)
+                                   (locally
+                                       (declare (optimize (safety 1)))
+                                     (the index
+                                       (,@check-form index)))))))
+           (define-setter (saetp check-form)
+             (let* ((type (sb!vm:saetp-specifier saetp))
+                    (atype `(simple-array ,type (*))))
+               `(named-lambda optimized-data-vector-set (vector index new-value)
+                  (declare (optimize speed (safety 0)))
+                  (data-vector-set (the ,atype vector)
+                                   (locally
+                                       (declare (optimize (safety 1)))
+                                     (the index
+                                       (,@check-form index)))
+                                   (locally
+                                       ;; SPEED 1 needed to avoid the compiler
+                                       ;; from downgrading the type check to
+                                       ;; a cheaper one.
+                                       (declare (optimize (speed 1)
+                                                          (safety 1)))
+                                     (the ,type new-value)))
+                  ;; For specialized arrays, the return from
+                  ;; data-vector-set would have to be reboxed to be a
+                  ;; (Lisp) return value; instead, we use the
+                  ;; already-boxed value as the return.
+                  new-value)))
+           (define-reffers (symbol deffer check-form slow-path)
+             `(progn
+                (setf ,symbol (make-array sb!vm::widetag-mask
+                                          :initial-element #'hairy-ref-error))
+                ,@(loop for widetag in '(sb!vm:complex-vector-widetag
+                                         sb!vm:complex-vector-nil-widetag
+                                         sb!vm:complex-bit-vector-widetag
+                                         #!+sb-unicode sb!vm:complex-character-string-widetag
+                                         sb!vm:complex-base-string-widetag
+                                         sb!vm:simple-array-widetag
+                                         sb!vm:complex-array-widetag)
+                        collect `(setf (svref ,symbol ,widetag) ,slow-path))
+                ,@(loop for saetp across sb!vm:*specialized-array-element-type-properties*
+                        for widetag = (sb!vm:saetp-typecode saetp)
+                        collect `(setf (svref ,symbol ,widetag)
+                                       (,deffer ,saetp ,check-form))))))
+  (defun !hairy-data-vector-reffer-init ()
+    (define-reffers *data-vector-reffers* define-reffer
+      (progn)
+      #'slow-hairy-data-vector-ref)
+    (define-reffers *data-vector-setters* define-setter
+      (progn)
+      #'slow-hairy-data-vector-set)
+    (define-reffers *data-vector-reffers/check-bounds* define-reffer
+      (%check-bound vector (length vector))
+      #'slow-hairy-data-vector-ref/check-bounds)
+    (define-reffers *data-vector-setters/check-bounds* define-setter
+      (%check-bound vector (length vector))
+      #'slow-hairy-data-vector-set/check-bounds)))
 
 ;;; (Ordinary DATA-VECTOR-REF usage compiles into a vop, but
 ;;; DATA-VECTOR-REF is also FOLDABLE, and this ordinary function
@@ -356,27 +473,8 @@ of specialized arrays is supported."
 (defun data-vector-ref (array index)
   (hairy-data-vector-ref array index))
 
-(defun hairy-data-vector-set (array index new-value)
-  (with-array-data ((vector array) (index index) (end))
-    (declare (ignore end))
-    (etypecase vector .
-               #.(map 'list
-                      (lambda (saetp)
-                        (let* ((type (sb!vm:saetp-specifier saetp))
-                               (atype `(simple-array ,type (*))))
-                          `(,atype
-                            (data-vector-set (the ,atype vector) index
-                                             (the ,type new-value))
-                            ;; For specialized arrays, the return from
-                            ;; data-vector-set would have to be
-                            ;; reboxed to be a (Lisp) return value;
-                            ;; instead, we use the already-boxed value
-                            ;; as the return.
-                            new-value)))
-                      (sort
-                       (copy-seq
-                        sb!vm:*specialized-array-element-type-properties*)
-                       #'> :key #'sb!vm:saetp-importance)))))
+(defun data-vector-ref-with-offset (array index offset)
+  (hairy-data-vector-ref array (+ index offset)))
 
 ;;; SUBSCRIPTS has a dynamic-extent list structure and is destroyed
 (defun %array-row-major-index (array subscripts
@@ -764,7 +862,11 @@ of specialized arrays is supported."
            (error "The number of dimensions not equal to rank of array."))
           ((not (subtypep element-type (array-element-type array)))
            (error "The new element type, ~S, is incompatible with old type."
-                  element-type)))
+                  element-type))
+          ((and fill-pointer (not (array-has-fill-pointer-p array)))
+           (error 'type-error
+                  :datum array
+                  :expected-type '(satisfies array-has-fill-pointer-p))))
     (let ((array-rank (length (the list dimensions))))
       (declare (fixnum array-rank))
       (unless (= array-rank 1)
@@ -980,44 +1082,62 @@ of specialized arrays is supported."
 ;;;
 ;;; DX is probably a bad idea, because a with a big array it would
 ;;; be fairly easy to blow the stack.
-;;;
-;;; Rebound per thread.
-(defvar *zap-array-data-temp* (make-array 1000 :initial-element t))
+(defvar *zap-array-data-temp* (vector))
+(declaim (simple-vector *zap-array-data-temp*))
 
-(defun zap-array-data-temp (length element-type initial-element
-                            initial-element-p)
+(defun zap-array-data-temp (length initial-element initial-element-p)
   (declare (fixnum length))
-  (when (> length (the fixnum (length *zap-array-data-temp*)))
-    (setf *zap-array-data-temp*
-          (make-array length :initial-element t)))
-  (when initial-element-p
-    (unless (typep initial-element element-type)
-      (error "~S can't be used to initialize an array of type ~S."
-             initial-element element-type))
-    (fill (the simple-vector *zap-array-data-temp*) initial-element
-          :end length))
-  *zap-array-data-temp*)
+  (let ((tmp *zap-array-data-temp*))
+    (declare (simple-vector tmp))
+    (cond ((> length (length tmp))
+           (setf *zap-array-data-temp*
+                 (if initial-element-p
+                     (make-array length :initial-element initial-element)
+                     (make-array length))))
+          (initial-element-p
+           (fill tmp initial-element :end length))
+          (t
+           tmp))))
 
 ;;; This does the grinding work for ADJUST-ARRAY. It zaps the data
 ;;; from the OLD-DATA in an arrangement specified by the OLD-DIMS to
 ;;; the NEW-DATA in an arrangement specified by the NEW-DIMS. OFFSET
 ;;; is a displaced offset to be added to computed indices of OLD-DATA.
-;;; NEW-LENGTH, ELEMENT-TYPE, INITIAL-ELEMENT, and INITIAL-ELEMENT-P
-;;; are used when OLD-DATA and NEW-DATA are EQ; in this case, a
-;;; temporary must be used and filled appropriately. When OLD-DATA and
-;;; NEW-DATA are not EQ, NEW-DATA has already been filled with any
-;;; specified initial-element.
 (defun zap-array-data (old-data old-dims offset new-data new-dims new-length
                        element-type initial-element initial-element-p)
   (declare (list old-dims new-dims))
-  (setq old-dims (nreverse old-dims))
-  (setq new-dims (reverse new-dims))
-  (if (eq old-data new-data)
-      (let ((temp (zap-array-data-temp new-length element-type
-                                       initial-element initial-element-p)))
-        (zap-array-data-aux old-data old-dims offset temp new-dims)
-        (dotimes (i new-length) (setf (aref new-data i) (aref temp i))))
-      (zap-array-data-aux old-data old-dims offset new-data new-dims)))
+  ;; OLD-DIMS comes from array-dimensions, which returns a fresh list
+  ;; at least in SBCL.
+  ;; NEW-DIMS comes from the user.
+  (setf old-dims (nreverse old-dims)
+        new-dims (reverse new-dims))
+  (cond ((eq old-data new-data)
+         ;; NEW-LENGTH, ELEMENT-TYPE, INITIAL-ELEMENT, and
+         ;; INITIAL-ELEMENT-P are used when OLD-DATA and NEW-DATA are
+         ;; EQ; in this case, a temporary must be used and filled
+         ;; appropriately. specified initial-element.
+         (when initial-element-p
+           ;; FIXME: transforming this TYPEP to someting a bit faster
+           ;; would be a win...
+           (unless (typep initial-element element-type)
+             (error "~S can't be used to initialize an array of type ~S."
+                    initial-element element-type)))
+         (without-interrupts
+           ;; Need to disable interrupts while using the temp-vector.
+           ;; An interrupt handler that also happened to call
+           ;; ADJUST-ARRAY could otherwise stomp on our data here.
+           (let ((temp (zap-array-data-temp new-length
+                                            initial-element initial-element-p)))
+             (declare (simple-vector temp))
+             (zap-array-data-aux old-data old-dims offset temp new-dims)
+             (dotimes (i new-length)
+               (setf (aref new-data i) (aref temp i)
+                     ;; zero out any garbage right away
+                     (aref temp i) 0)))))
+        (t
+         ;; When OLD-DATA and NEW-DATA are not EQ, NEW-DATA has
+         ;; already been filled with any
+         (zap-array-data-aux old-data old-dims offset new-data new-dims))))
 
 (defun zap-array-data-aux (old-data old-dims offset new-data new-dims)
   (declare (fixnum offset))