add DO-VECTOR-DATA, remove special case from VECTOR-MAP-INTO
[sbcl.git] / src / code / array.lisp
index b1239ca..0d44b09 100644 (file)
@@ -12,7 +12,7 @@
 (in-package "SB!IMPL")
 
 #!-sb-fluid
-(declaim (inline fill-pointer array-has-fill-pointer-p adjustable-array-p
+(declaim (inline adjustable-array-p
                  array-displacement))
 \f
 ;;;; miscellaneous accessor functions
@@ -30,7 +30,8 @@
   (def %array-available-elements)
   (def %array-data-vector)
   (def %array-displacement)
-  (def %array-displaced-p))
+  (def %array-displaced-p)
+  (def %array-diplaced-from))
 
 (defun %array-rank (array)
   (%array-rank array))
@@ -95,6 +96,8 @@
      (values #.sb!vm:simple-bit-vector-widetag 1))
     ;; OK, we have to wade into SUBTYPEPing after all.
     (t
+     (unless *type-system-initialized*
+       (bug "SUBTYPEP dispatch for MAKE-ARRAY before the type system is ready"))
      #.`(pick-vector-type type
          ,@(map 'list
                 (lambda (saetp)
                  (setf (%array-fill-pointer-p array) nil)))
           (setf (%array-available-elements array) total-size)
           (setf (%array-data-vector array) data)
+          (setf (%array-displaced-from array) nil)
           (cond (displaced-to
                  (when (or initial-element-p initial-contents-p)
                    (error "Neither :INITIAL-ELEMENT nor :INITIAL-CONTENTS ~
                             (array-total-size displaced-to))
                      (error "~S doesn't have enough elements." displaced-to))
                    (setf (%array-displacement array) offset)
-                   (setf (%array-displaced-p array) t)))
+                   (setf (%array-displaced-p array) t)
+                   (%save-displaced-array-backpointer array data)))
                 (t
                  (setf (%array-displaced-p array) nil)))
           (let ((axis 0))
@@ -325,31 +330,38 @@ of specialized arrays is supported."
 ;;; vectors or not simple.
 (macrolet ((def (name table-name)
              `(progn
-                (defvar ,table-name)
+                (defglobal ,table-name (make-array ,(1+ sb!vm:widetag-mask)))
                 (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*))
+                  `(the function
+                     (let ((tag 0))
+                       (when (sb!vm::%other-pointer-p ,array-var)
+                         (setf tag (%other-pointer-widetag ,array-var)))
+                       (svref ,',table-name tag)))))))
+  (def !find-data-vector-setter %%data-vector-setters%%)
+  (def !find-data-vector-setter/check-bounds %%data-vector-setters/check-bounds%%)
+  ;; Used by DO-VECTOR-DATA -- which in turn appears in DOSEQUENCE expansion,
+  ;; meaning we can have post-build dependences on this.
+  (def %find-data-vector-reffer %%data-vector-reffers%%)
+  (def !find-data-vector-reffer/check-bounds %%data-vector-reffers/check-bounds%%))
+
+;;; Like DOVECTOR, but more magical -- can't use this on host.
+(defmacro do-vector-data ((elt vector &optional result) &body body)
+  (multiple-value-bind (forms decls) (parse-body body :doc-string-allowed nil)
+    (with-unique-names (index vec start end ref)
+      `(with-array-data ((,vec ,vector)
+                         (,start)
+                         (,end)
+                         :check-fill-pointer t)
+         (let ((,ref (%find-data-vector-reffer ,vec)))
+           (do ((,index ,start (1+ ,index)))
+               ((>= ,index ,end)
+                (let ((,elt nil))
+                  ,@(filter-dolist-declarations decls)
+                  ,elt
+                  ,result))
+             (let ((,elt (funcall ,ref ,vec ,index)))
+               ,@decls
+               (tagbody ,@forms))))))))
 
 (macrolet ((%ref (accessor-getter extra-params)
              `(funcall (,accessor-getter array) array index ,@extra-params))
@@ -384,7 +396,7 @@ of specialized arrays is supported."
                         (declare (ignore end))
                         (,accessor-name vector index ,@extra-params)))))))
   (define hairy-data-vector-ref slow-hairy-data-vector-ref
-    !find-data-vector-reffer
+    %find-data-vector-reffer
     nil (progn))
   (define hairy-data-vector-set slow-hairy-data-vector-set
     !find-data-vector-setter
@@ -404,7 +416,6 @@ of specialized arrays is supported."
          :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 (*))))
@@ -439,7 +450,10 @@ of specialized arrays is supported."
                   new-value)))
            (define-reffers (symbol deffer check-form slow-path)
              `(progn
-                (setf ,symbol (make-array sb!vm::widetag-mask
+                ;; FIXME/KLUDGE: can't just FILL here, because genesis doesn't
+                ;; preserve the binding, so re-initiaize as NS doesn't have
+                ;; the energy to figure out to change that right now.
+                (setf ,symbol (make-array (1+ sb!vm::widetag-mask)
                                           :initial-element #'hairy-ref-error))
                 ,@(loop for widetag in '(sb!vm:complex-vector-widetag
                                          sb!vm:complex-vector-nil-widetag
@@ -454,16 +468,16 @@ of specialized arrays is supported."
                         collect `(setf (svref ,symbol ,widetag)
                                        (,deffer ,saetp ,check-form))))))
   (defun !hairy-data-vector-reffer-init ()
-    (define-reffers *data-vector-reffers* define-reffer
+    (define-reffers %%data-vector-reffers%% define-reffer
       (progn)
       #'slow-hairy-data-vector-ref)
-    (define-reffers *data-vector-setters* define-setter
+    (define-reffers %%data-vector-setters%% define-setter
       (progn)
       #'slow-hairy-data-vector-set)
-    (define-reffers *data-vector-reffers/check-bounds* define-reffer
+    (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
+    (define-reffers %%data-vector-setters/check-bounds%% define-setter
       (%check-bound vector (length vector))
       #'slow-hairy-data-vector-set/check-bounds)))
 
@@ -476,6 +490,34 @@ of specialized arrays is supported."
 (defun data-vector-ref-with-offset (array index offset)
   (hairy-data-vector-ref array (+ index offset)))
 
+(defun invalid-array-p (array)
+  (and (array-header-p array)
+       (consp (%array-displaced-p array))))
+
+(declaim (ftype (function (array) nil) invalid-array-error))
+(defun invalid-array-error (array)
+  (aver (array-header-p array))
+  ;; Array invalidation stashes the original dimensions here...
+  (let ((dims (%array-displaced-p array))
+        (et (array-element-type array)))
+    (error 'invalid-array-error
+           :datum array
+           :expected-type
+           (if (cdr dims)
+               `(array ,et ,dims)
+               `(vector ,et ,@dims)))))
+
+(declaim (ftype (function (array integer integer &optional t) nil)
+                invalid-array-index-error))
+(defun invalid-array-index-error (array index bound &optional axis)
+  (if (invalid-array-p array)
+      (invalid-array-error array)
+      (error 'invalid-array-index-error
+             :array array
+             :axis axis
+             :datum index
+             :expected-type `(integer 0 (,bound)))))
+
 ;;; SUBSCRIPTS has a dynamic-extent list structure and is destroyed
 (defun %array-row-major-index (array subscripts
                                      &optional (invalid-index-error-p t))
@@ -497,11 +539,7 @@ of specialized arrays is supported."
             (declare (fixnum dim))
             (unless (and (fixnump index) (< -1 index dim))
               (if invalid-index-error-p
-                  (error 'simple-type-error
-                         :format-control "invalid index ~W~[~;~:; on axis ~:*~W~] in ~S"
-                         :format-arguments (list index axis array)
-                         :datum index
-                         :expected-type `(integer 0 (,dim)))
+                  (invalid-array-index-error array index dim axis)
                   (return-from %array-row-major-index nil)))
             (incf result (* chunk-size (the fixnum index)))
             (setf chunk-size (* chunk-size dim))))
@@ -509,20 +547,13 @@ of specialized arrays is supported."
               (length (length (the (simple-array * (*)) array))))
           (unless (and (fixnump index) (< -1 index length))
             (if invalid-index-error-p
-                ;; FIXME: perhaps this should share a format-string
-                ;; with INVALID-ARRAY-INDEX-ERROR or
-                ;; INDEX-TOO-LARGE-ERROR?
-                (error 'simple-type-error
-                       :format-control "invalid index ~W in ~S"
-                       :format-arguments (list index array)
-                       :datum index
-                       :expected-type `(integer 0 (,length)))
+                (invalid-array-index-error array index length)
                 (return-from %array-row-major-index nil)))
           index))))
 
 (defun array-in-bounds-p (array &rest subscripts)
   #!+sb-doc
-  "Return T if the SUBSCIPTS are in bounds for the ARRAY, NIL otherwise."
+  "Return T if the SUBSCRIPTS are in bounds for the ARRAY, NIL otherwise."
   (if (%array-row-major-index array subscripts nil)
       t))
 
@@ -701,25 +732,7 @@ of specialized arrays is supported."
          (error "Axis number ~W is too big; ~S only has ~D dimension~:P."
                 axis-number array (%array-rank array)))
         (t
-         ;; ANSI sayeth (ADJUST-ARRAY dictionary entry):
-         ;;
-         ;;   "If A is displaced to B, the consequences are
-         ;;   unspecified if B is adjusted in such a way that it no
-         ;;   longer has enough elements to satisfy A.
-         ;;
-         ;; In situations where this matters we should be doing a
-         ;; bounds-check, which in turn uses ARRAY-DIMENSION -- so
-         ;; this seems like a good place to signal an error.
-         (multiple-value-bind (target offset) (array-displacement array)
-           (when (and target
-                      (> (array-total-size array)
-                         (- (array-total-size target) offset)))
-               (error 'displaced-to-array-too-small-error
-                      :format-control "~@<The displaced-to array is too small. ~S ~
-                                      elements after offset required, ~S available.~:@>"
-                      :format-arguments (list (array-total-size array)
-                                              (- (array-total-size target) offset))))
-           (%array-dimension array axis-number)))))
+         (%array-dimension array axis-number))))
 
 (defun array-dimensions (array)
   #!+sb-doc
@@ -762,6 +775,7 @@ of specialized arrays is supported."
 \f
 ;;;; fill pointer frobbing stuff
 
+(declaim (inline array-has-fill-pointer-p))
 (defun array-has-fill-pointer-p (array)
   #!+sb-doc
   "Return T if the given ARRAY has a fill pointer, or NIL otherwise."
@@ -784,6 +798,7 @@ of specialized arrays is supported."
                 :format-control "~S is not an array with a fill pointer."
                 :format-arguments (list vector)))))
 
+(declaim (inline fill-pointer))
 (defun fill-pointer (vector)
   #!+sb-doc
   "Return the FILL-POINTER of the given VECTOR."
@@ -811,7 +826,6 @@ of specialized arrays is supported."
    to NEW-EL, and increment the fill pointer by one. If the fill pointer is
    too large, NIL is returned, otherwise the index of the pushed element is
    returned."
-  (declare (vector array))
   (let ((fill-pointer (fill-pointer array)))
     (declare (fixnum fill-pointer))
     (cond ((= fill-pointer (%array-available-elements array))
@@ -829,7 +843,7 @@ of specialized arrays is supported."
                             (let ((length (length vector)))
                               (min (1+ length)
                                    (- array-dimension-limit length)))))
-  (declare (vector vector) (fixnum min-extension))
+  (declare (fixnum min-extension))
   (let ((fill-pointer (fill-pointer vector)))
     (declare (fixnum fill-pointer))
     (when (= fill-pointer (%array-available-elements vector))
@@ -844,7 +858,6 @@ of specialized arrays is supported."
   #!+sb-doc
   "Decrease the fill pointer by 1 and return the element pointed to by the
   new fill pointer."
-  (declare (vector array))
   (let ((fill-pointer (fill-pointer array)))
     (declare (fixnum fill-pointer))
     (if (zerop fill-pointer)
@@ -866,6 +879,8 @@ of specialized arrays is supported."
                            displaced-to displaced-index-offset)
   #!+sb-doc
   "Adjust ARRAY's dimensions to the given DIMENSIONS and stuff."
+  (when (invalid-array-p array)
+    (invalid-array-error array))
   (let ((dimensions (if (listp dimensions) dimensions (list dimensions))))
     (cond ((/= (the fixnum (length (the list dimensions)))
                (the fixnum (array-rank array)))
@@ -896,7 +911,7 @@ of specialized arrays is supported."
                    (set-array-header array array-data array-size
                                  (get-new-fill-pointer array array-size
                                                        fill-pointer)
-                                 0 dimensions nil)
+                                 0 dimensions nil nil)
                    (if (array-header-p array)
                        ;; simple multidimensional or single dimensional array
                        (make-array dimensions
@@ -923,7 +938,7 @@ of specialized arrays is supported."
                    (set-array-header array displaced-to array-size
                                      (get-new-fill-pointer array array-size
                                                            fill-pointer)
-                                     displacement dimensions t)
+                                     displacement dimensions t nil)
                    ;; simple multidimensional or single dimensional array
                    (make-array dimensions
                                :element-type element-type
@@ -953,7 +968,7 @@ of specialized arrays is supported."
                      (set-array-header array new-data new-length
                                        (get-new-fill-pointer array new-length
                                                              fill-pointer)
-                                       0 dimensions nil)
+                                       0 dimensions nil nil)
                      new-data))))
             (t
              (let ((old-length (%array-available-elements array))
@@ -979,12 +994,12 @@ of specialized arrays is supported."
                                        initial-element-p))
                    (if (adjustable-array-p array)
                        (set-array-header array new-data new-length
-                                         nil 0 dimensions nil)
+                                         nil 0 dimensions nil nil)
                        (let ((new-array
                               (make-array-header
                                sb!vm:simple-array-widetag array-rank)))
                          (set-array-header new-array new-data new-length
-                                           nil 0 dimensions nil)))))))))))
+                                           nil 0 dimensions nil t)))))))))))
 
 
 (defun get-new-fill-pointer (old-array new-array-size fill-pointer)
@@ -1064,9 +1079,76 @@ of specialized arrays is supported."
      vector)
     (t (subseq vector 0 new-length))))
 
+;;; BIG THREAD SAFETY NOTE
+;;;
+;;; ADJUST-ARRAY/SET-ARRAY-HEADER, and its callees are very
+;;; thread unsafe. They are nonatomic, and can mess with parallel
+;;; code using the same arrays.
+;;;
+;;; A likely seeming fix is an additional level of indirection:
+;;; ARRAY-HEADER -> ARRAY-INFO -> ... where ARRAY-HEADER would
+;;; hold nothing but the pointer to ARRAY-INFO, and ARRAY-INFO
+;;; would hold everything ARRAY-HEADER now holds. This allows
+;;; consing up a new ARRAY-INFO and replacing it atomically in
+;;; the ARRAY-HEADER.
+;;;
+;;; %WALK-DISPLACED-ARRAY-BACKPOINTERS is an especially nasty
+;;; one: not only is it needed extremely rarely, which makes
+;;; any thread safety bugs involving it look like rare random
+;;; corruption, but because it walks the chain *upwards*, which
+;;; may violate user expectations.
+
+(defun %save-displaced-array-backpointer (array data)
+  (flet ((purge (pointers)
+           (remove-if (lambda (value)
+                        (or (not value) (eq array value)))
+                      pointers
+                      :key #'weak-pointer-value)))
+    ;; Add backpointer to the new data vector if it has a header.
+    (when (array-header-p data)
+      (setf (%array-displaced-from data)
+            (cons (make-weak-pointer array)
+                  (purge (%array-displaced-from data)))))
+    ;; Remove old backpointer, if any.
+    (let ((old-data (%array-data-vector array)))
+      (when (and (neq data old-data) (array-header-p old-data))
+        (setf (%array-displaced-from old-data)
+              (purge (%array-displaced-from old-data)))))))
+
+(defun %walk-displaced-array-backpointers (array new-length)
+  (dolist (p (%array-displaced-from array))
+    (let ((from (weak-pointer-value p)))
+      (when (and from (eq array (%array-data-vector from)))
+        (let ((requires (+ (%array-available-elements from)
+                           (%array-displacement from))))
+          (unless (>= new-length requires)
+            ;; ANSI sayeth (ADJUST-ARRAY dictionary entry):
+            ;;
+            ;;   "If A is displaced to B, the consequences are unspecified if B is
+            ;;   adjusted in such a way that it no longer has enough elements to
+            ;;   satisfy A.
+            ;;
+            ;; since we're hanging on a weak pointer here, we can't signal an
+            ;; error right now: the array that we're looking at might be
+            ;; garbage. Instead, we set all dimensions to zero so that next
+            ;; safe access to the displaced array will trap. Additionally, we
+            ;; save the original dimensions, so we can signal a more
+            ;; understandable error when the time comes.
+            (%walk-displaced-array-backpointers from 0)
+            (setf (%array-fill-pointer from) 0
+                  (%array-available-elements from) 0
+                  (%array-displaced-p from) (array-dimensions array))
+            (dotimes (i (%array-rank from))
+              (setf (%array-dimension from i) 0))))))))
+
 ;;; Fill in array header with the provided information, and return the array.
 (defun set-array-header (array data length fill-pointer displacement dimensions
-                         &optional displacedp)
+                         displacedp newp)
+  (if newp
+      (setf (%array-displaced-from array) nil)
+      (%walk-displaced-array-backpointers array length))
+  (when displacedp
+    (%save-displaced-array-backpointer array data))
   (setf (%array-data-vector array) data)
   (setf (%array-available-elements array) length)
   (cond (fill-pointer
@@ -1085,68 +1167,40 @@ of specialized arrays is supported."
   array)
 
 ;;; User visible extension
-(declaim (ftype (function (simple-array) (values (simple-array * (*)) &optional))
-                simple-array-vector))
-(defun simple-array-vector (array)
-  "Returns the one-dimensional SIMPLE-ARRAY corresponding to ARRAY.
+(declaim (ftype (function (array) (values (simple-array * (*)) &optional))
+                array-storage-vector))
+(defun array-storage-vector (array)
+  "Returns the underlying storage vector of ARRAY, which must be a non-displaced array.
 
-The ARRAY must be a SIMPLE-ARRAY. If ARRAY is multidimensional, returns the
-underlying one-dimensional SIMPLE-ARRAY which shares storage with ARRAY.
-Otherwise returns ARRAY.
-
-Currently in SBCL a multidimensional SIMPLE-ARRAY has an underlying
-one-dimensional SIMPLE-ARRAY, which holds the data in row major order. This
-function provides access to that vector.
+In SBCL, if ARRAY is a of type \(SIMPLE-ARRAY * \(*)), it is its own storage
+vector. Multidimensional arrays, arrays with fill pointers, and adjustable
+arrays have an underlying storage vector with the same ARRAY-ELEMENT-TYPE as
+ARRAY, which this function returns.
 
 Important note: the underlying vector is an implementation detail. Even though
 this function exposes it, changes in the implementation may cause this
 function to be removed without further warning."
   ;; KLUDGE: Without TRULY-THE the system is not smart enough to figure out that
-  ;; (1) SIMPLE-ARRAY without ARRAY-HEADER-P is a vector (2) the data vector of
-  ;; a SIMPLE-ARRAY is a vector.
+  ;; the return value is always of the known type.
   (truly-the (simple-array * (*))
              (if (array-header-p array)
-                 (%array-data-vector array)
+                 (if (%array-displaced-p array)
+                     (error "~S cannot be used with displaced arrays. Use ~S instead."
+                            'array-storage-vector 'array-displacement)
+                     (%array-data-vector array))
                  array)))
 \f
-;;;; used by SORT
-
-;;; temporary vector for stable sorting vectors, allocated for each new thread
-(defvar *merge-sort-temp-vector* (vector))
-(declaim (simple-vector *merge-sort-temp-vector*))
 
 ;;;; ZAP-ARRAY-DATA for ADJUST-ARRAY
 
-;;; a temporary to be used when OLD-DATA and NEW-DATA are EQ.
-;;; KLUDGE: Boy, DYNAMIC-EXTENT would be nice. This is rebound
-;;; to length zero array in each new thread.
-;;;
-;;; DX is probably a bad idea, because a with a big array it would
-;;; be fairly easy to blow the stack.
-(defvar *zap-array-data-temp* (vector))
-(declaim (simple-vector *zap-array-data-temp*))
-
-(defun zap-array-data-temp (length initial-element initial-element-p)
-  (declare (fixnum length))
-  (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.
 (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))
+  (declare (list old-dims new-dims)
+           (fixnum new-length))
   ;; OLD-DIMS comes from array-dimensions, which returns a fresh list
   ;; at least in SBCL.
   ;; NEW-DIMS comes from the user.
@@ -1163,14 +1217,15 @@ function to be removed without further warning."
            (unless (typep initial-element element-type)
              (error "~S can't be used to initialize an array of type ~S."
                     initial-element element-type)))
-         (let ((temp (zap-array-data-temp new-length
-                                          initial-element initial-element-p)))
+         (let ((temp (if initial-element-p
+                         (make-array new-length :initial-element initial-element)
+                         (make-array new-length))))
            (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))))
+             (setf (aref new-data i) (aref temp i)))
+           ;; Kill the temporary vector to prevent garbage retention.
+           (%shrink-vector temp 0)))
         (t
          ;; When OLD-DATA and NEW-DATA are not EQ, NEW-DATA has
          ;; already been filled with any
@@ -1309,3 +1364,59 @@ function to be removed without further warning."
               (declare (type index src-index dst-index))
               (setf (sbit dst dst-index)
                     (logxor (sbit src src-index) 1))))))))
+
+;;;; array type dispatching
+
+;;; Given DISPATCH-FOO as the DISPATCH-NAME argument (unevaluated),
+;;; defines the functions
+;;;
+;;; DISPATCH-FOO/SIMPLE-BASE-STRING
+;;; DISPATCH-FOO/SIMPLE-CHARACTER-STRING
+;;; DISPATCH-FOO/SIMPLE-ARRAY-SINGLE-FLOAT
+;;; ...
+;;;
+;;; PARAMS are the function parameters in the definition of each
+;;; specializer function. The array being specialized must be the
+;;; first parameter in PARAMS. A type declaration for this parameter
+;;; is automatically inserted into the body of each function.
+;;;
+;;; The dispatch table %%FOO-FUNS%% is defined and populated by these
+;;; functions. The table is padded by the function
+;;; HAIRY-FOO-DISPATCH-ERROR, also defined by DEFINE-ARRAY-DISPATCH.
+;;;
+;;; Finally, the DISPATCH-FOO macro is defined which does the actual
+;;; dispatching when called. It expects arguments that match PARAMS.
+;;;
+(defmacro define-array-dispatch (dispatch-name params &body body)
+  (let ((table-name (symbolicate "%%" dispatch-name "-FUNS%%"))
+        (error-name (symbolicate "HAIRY-" dispatch-name "-ERROR")))
+    `(progn
+       (eval-when (:compile-toplevel :load-toplevel :execute)
+         (defun ,error-name (&rest args)
+           (error 'type-error
+                  :datum (first args)
+                  :expected-type '(simple-array * (*)))))
+       (defglobal ,table-name (make-array ,(1+ sb!vm:widetag-mask)
+                                          :initial-element #',error-name))
+       ,@(loop for info across sb!vm:*specialized-array-element-type-properties*
+               for typecode = (sb!vm:saetp-typecode info)
+               for specifier = (sb!vm:saetp-specifier info)
+               for primitive-type-name = (sb!vm:saetp-primitive-type-name info)
+               collect (let ((fun-name (symbolicate (string dispatch-name)
+                                                    "/" primitive-type-name)))
+                         `(progn
+                            (defun ,fun-name ,params
+                              (declare (type (simple-array ,specifier (*))
+                                             ,(first params)))
+                              ,@body)
+                            (setf (svref ,table-name ,typecode) #',fun-name))))
+       (defmacro ,dispatch-name (&rest args)
+         (check-type (first args) symbol)
+         (let ((tag (gensym "TAG")))
+           `(funcall
+             (the function
+               (let ((,tag 0))
+                 (when (sb!vm::%other-pointer-p ,(first args))
+                   (setf ,tag (%other-pointer-widetag ,(first args))))
+                 (svref ,',table-name ,tag)))
+             ,@args))))))