X-Git-Url: http://repo.macrolet.net/gitweb/?a=blobdiff_plain;f=src%2Fcode%2Farray.lisp;h=02425d1048b4824aaaa5a95aae3e64d2fdfc40d2;hb=b14a61c6af3e3005c94e633e727177346240066e;hp=817bdb783c80e0e68733a28ea48910598024f6ff;hpb=bfb19d306581ac86feb4371846c4b9953d692dd8;p=sbcl.git diff --git a/src/code/array.lisp b/src/code/array.lisp index 817bdb7..02425d1 100644 --- a/src/code/array.lisp +++ b/src/code/array.lisp @@ -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)) ;;;; 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)) @@ -46,8 +47,11 @@ (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) @@ -55,14 +59,6 @@ (%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?")) ;;;; MAKE-ARRAY (eval-when (:compile-toplevel :execute) @@ -100,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) @@ -135,6 +133,28 @@ (bit #.sb!vm:complex-bit-vector-widetag) (t #.sb!vm:complex-vector-widetag))))) +(defglobal %%simple-array-n-bits%% (make-array (1+ sb!vm:widetag-mask))) +#.(loop for info across sb!vm:*specialized-array-element-type-properties* + collect `(setf (aref %%simple-array-n-bits%% ,(sb!vm:saetp-typecode info)) + ,(sb!vm:saetp-n-bits info)) into forms + finally (return `(progn ,@forms))) + +(defun allocate-vector-with-widetag (widetag length &optional n-bits) + (declare (type (unsigned-byte 8) widetag) + (type index length)) + (let ((n-bits (or n-bits (aref %%simple-array-n-bits%% widetag)))) + (declare (type (integer 0 256) n-bits)) + (allocate-vector widetag length + (ceiling + (* (if (or (= widetag sb!vm:simple-base-string-widetag) + #!+sb-unicode + (= widetag + sb!vm:simple-character-string-widetag)) + (1+ length) + length) + n-bits) + sb!vm:n-word-bits)))) + (defun make-array (dimensions &key (element-type t) (initial-element nil initial-element-p) @@ -161,18 +181,7 @@ (declare (type (unsigned-byte 8) type) (type (integer 0 256) n-bits)) (let* ((length (car dimensions)) - (array (allocate-vector - type - length - (ceiling - (* (if (or (= type sb!vm:simple-base-string-widetag) - #!+sb-unicode - (= type - sb!vm:simple-character-string-widetag)) - (1+ length) - length) - n-bits) - sb!vm:n-word-bits)))) + (array (allocate-vector-with-widetag type length n-bits))) (declare (type index length)) (when initial-element-p (fill array initial-element)) @@ -191,7 +200,7 @@ (let* ((total-size (reduce #'* dimensions)) (data (or displaced-to (data-vector-from-inits - dimensions total-size element-type + dimensions total-size element-type nil initial-contents initial-contents-p initial-element initial-element-p))) (array (make-array-header @@ -222,6 +231,7 @@ (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 ~ @@ -231,7 +241,8 @@ (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)) @@ -289,24 +300,22 @@ of specialized arrays is supported." ;;; specified array characteristics. Dimensions is only used to pass ;;; to FILL-DATA-VECTOR for error checking on the structure of ;;; initial-contents. -(defun data-vector-from-inits (dimensions total-size element-type +(defun data-vector-from-inits (dimensions total-size + element-type widetag initial-contents initial-contents-p initial-element initial-element-p) - (when (and initial-contents-p initial-element-p) - (error "cannot supply both :INITIAL-CONTENTS and :INITIAL-ELEMENT to + (when initial-element-p + (when initial-contents-p + (error "cannot supply both :INITIAL-CONTENTS and :INITIAL-ELEMENT to either MAKE-ARRAY or ADJUST-ARRAY.")) - (let ((data (if initial-element-p - (make-array total-size - :element-type element-type - :initial-element initial-element) - (make-array total-size - :element-type element-type)))) + (unless (typep initial-element element-type) + (error "~S cannot be used to initialize an array of type ~S." + initial-element element-type))) + (let ((data (if widetag + (allocate-vector-with-widetag widetag total-size) + (make-array total-size :element-type element-type)))) (cond (initial-element-p - (unless (simple-vector-p data) - (unless (typep initial-element element-type) - (error "~S cannot be used to initialize an array of type ~S." - initial-element element-type)) - (fill (the vector data) initial-element))) + (fill (the vector data) initial-element)) (initial-contents-p (fill-data-vector data dimensions initial-contents))) data)) @@ -328,71 +337,87 @@ of specialized arrays is supported." ;;; 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 ((%define (table-name extra-params) - `(funcall - (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) - (setf tag - (sb!sys:sap-ref-8 (int-sap (get-lisp-obj-address array)) - offset))) - ;; SYMBOL-GLOBAL-VALUE is a performance hack - ;; for threaded builds. - (svref (sb!vm::symbol-global-value ',table-name) tag))) - array index ,@extra-params)) - (define (accessor-name slow-accessor-name table-name extra-params - check-bounds) - `(progn - (defvar ,table-name) - (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))) - (%define ,table-name ,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))) - (%define ,table-name ,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))))))) +(macrolet ((def (name table-name) + `(progn + (defglobal ,table-name (make-array ,(1+ sb!vm:widetag-mask))) + (defmacro ,name (array-var) + `(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)) + (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 - *data-vector-reffers* nil (progn)) + %find-data-vector-reffer + nil (progn)) (define hairy-data-vector-set slow-hairy-data-vector-set - *data-vector-setters* (new-value) (progn)) + !find-data-vector-setter + (new-value) (progn)) (define hairy-data-vector-ref/check-bounds slow-hairy-data-vector-ref/check-bounds - *data-vector-reffers/check-bounds* nil - (%check-bound array (array-dimension array 0))) + !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 - *data-vector-setters/check-bounds* (new-value) - (%check-bound array (array-dimension array 0)))) + !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)) @@ -400,7 +425,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 (*)))) @@ -435,7 +459,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 @@ -450,16 +477,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))) @@ -472,6 +499,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)) @@ -493,11 +548,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)))) @@ -505,76 +556,41 @@ 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)) (defun array-row-major-index (array &rest subscripts) - (declare (dynamic-extent subscripts)) + (declare (truly-dynamic-extent subscripts)) (%array-row-major-index array subscripts)) (defun aref (array &rest subscripts) #!+sb-doc "Return the element of the ARRAY specified by the SUBSCRIPTS." - (declare (dynamic-extent subscripts)) + (declare (truly-dynamic-extent subscripts)) (row-major-aref array (%array-row-major-index array subscripts))) -(defun %aset (array &rest stuff) - (declare (dynamic-extent stuff)) - (let ((subscripts (butlast stuff)) - (new-value (car (last stuff)))) - (setf (row-major-aref array (%array-row-major-index array subscripts)) - new-value))) - -;;; FIXME: What's supposed to happen with functions -;;; like AREF when we (DEFUN (SETF FOO) ..) when -;;; DEFSETF FOO is also defined? It seems as though the logical -;;; thing to do would be to nuke the macro definition for (SETF FOO) -;;; and replace it with the (SETF FOO) function, issuing a warning, -;;; just as for ordinary functions -;;; * (LISP-IMPLEMENTATION-VERSION) -;;; "18a+ release x86-linux 2.4.7 6 November 1998 cvs" -;;; * (DEFMACRO ZOO (X) `(+ ,X ,X)) -;;; ZOO -;;; * (DEFUN ZOO (X) (* 3 X)) -;;; Warning: ZOO previously defined as a macro. -;;; ZOO -;;; But that doesn't seem to be what happens in CMU CL. -;;; -;;; KLUDGE: this is probably because ANSI, in its wisdom (CLHS -;;; 5.1.2.5) requires implementations to support -;;; (SETF (APPLY #'AREF ...) ...) -;;; [and also #'BIT and #'SBIT]. Yes, this is terrifying, and it's -;;; also terrifying that this sequence of definitions causes it to -;;; work. -;;; -;;; Also, it would be nice to make DESCRIBE FOO tell whether a symbol -;;; has a setf expansion and/or a setf function defined. - -#!-sb-fluid (declaim (inline (setf aref))) +;;; (setf aref/bit/sbit) are implemented using setf-functions, +;;; because they have to work with (setf (apply #'aref array subscripts)) +;;; All other setfs can be done using setf-functions too, but I +;;; haven't found technical advantages or disatvantages for either +;;; scheme. (defun (setf aref) (new-value array &rest subscripts) - (declare (dynamic-extent subscripts)) - (declare (type array array)) + (declare (truly-dynamic-extent subscripts) + (type array array)) (setf (row-major-aref array (%array-row-major-index array subscripts)) new-value)) (defun row-major-aref (array index) #!+sb-doc - "Return the element of array corressponding to the row-major index. This is - SETF'able." + "Return the element of array corresponding to the row-major index. This is + SETFable." (declare (optimize (safety 1))) (row-major-aref array index)) @@ -584,7 +600,7 @@ of specialized arrays is supported." (defun svref (simple-vector index) #!+sb-doc - "Return the INDEX'th element of the given Simple-Vector." + "Return the INDEXth element of the given Simple-Vector." (declare (optimize (safety 1))) (aref simple-vector index)) @@ -595,20 +611,14 @@ of specialized arrays is supported." (defun bit (bit-array &rest subscripts) #!+sb-doc "Return the bit from the BIT-ARRAY at the specified SUBSCRIPTS." - (declare (type (array bit) bit-array) (optimize (safety 1))) + (declare (type (array bit) bit-array) + (optimize (safety 1))) (row-major-aref bit-array (%array-row-major-index bit-array subscripts))) -(defun %bitset (bit-array &rest stuff) - (declare (type (array bit) bit-array) (optimize (safety 1))) - (let ((subscripts (butlast stuff)) - (new-value (car (last stuff)))) - (setf (row-major-aref bit-array - (%array-row-major-index bit-array subscripts)) - new-value))) - -#!-sb-fluid (declaim (inline (setf bit))) (defun (setf bit) (new-value bit-array &rest subscripts) - (declare (type (array bit) bit-array) (optimize (safety 1))) + (declare (type (array bit) bit-array) + (type bit new-value) + (optimize (safety 1))) (setf (row-major-aref bit-array (%array-row-major-index bit-array subscripts)) new-value)) @@ -616,25 +626,15 @@ of specialized arrays is supported." (defun sbit (simple-bit-array &rest subscripts) #!+sb-doc "Return the bit from SIMPLE-BIT-ARRAY at the specified SUBSCRIPTS." - (declare (type (simple-array bit) simple-bit-array) (optimize (safety 1))) + (declare (type (simple-array bit) simple-bit-array) + (optimize (safety 1))) (row-major-aref simple-bit-array (%array-row-major-index simple-bit-array subscripts))) -;;; KLUDGE: Not all these things (%SET-ROW-MAJOR-AREF, %SET-FILL-POINTER, -;;; %SET-FDEFINITION, %SCHARSET, %SBITSET..) seem to deserve separate names. -;;; Could we just DEFUN (SETF SBIT) etc. and get rid of the non-ANSI names? -;;; -- WHN 19990911 -(defun %sbitset (simple-bit-array &rest stuff) - (declare (type (simple-array bit) simple-bit-array) (optimize (safety 1))) - (let ((subscripts (butlast stuff)) - (new-value (car (last stuff)))) - (setf (row-major-aref simple-bit-array - (%array-row-major-index simple-bit-array subscripts)) - new-value))) - -#!-sb-fluid (declaim (inline (setf sbit))) (defun (setf sbit) (new-value bit-array &rest subscripts) - (declare (type (simple-array bit) bit-array) (optimize (safety 1))) + (declare (type (simple-array bit) bit-array) + (type bit new-value) + (optimize (safety 1))) (setf (row-major-aref bit-array (%array-row-major-index bit-array subscripts)) new-value)) @@ -697,25 +697,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 "~@" - :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 @@ -758,68 +740,78 @@ of specialized arrays is supported." ;;;; 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." (declare (array array)) (and (array-header-p array) (%array-fill-pointer-p array))) +(defun fill-pointer-error (vector arg) + (cond (arg + (aver (array-has-fill-pointer-p vector)) + (let ((max (%array-available-elements vector))) + (error 'simple-type-error + :datum arg + :expected-type (list 'integer 0 max) + :format-control "The new fill pointer, ~S, is larger than the length of the vector (~S.)" + :format-arguments (list arg max)))) + (t + (error 'simple-type-error + :datum vector + :expected-type '(and vector (satisfies array-has-fill-pointer-p)) + :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." - (declare (vector vector)) - (if (and (array-header-p vector) (%array-fill-pointer-p vector)) + (if (array-has-fill-pointer-p vector) (%array-fill-pointer vector) - (error 'simple-type-error - :datum vector - :expected-type '(and vector (satisfies array-has-fill-pointer-p)) - :format-control "~S is not an array with a fill pointer." - :format-arguments (list vector)))) + (fill-pointer-error vector nil))) (defun %set-fill-pointer (vector new) - (declare (vector vector) (fixnum new)) - (if (and (array-header-p vector) (%array-fill-pointer-p vector)) - (if (> new (%array-available-elements vector)) - (error - "The new fill pointer, ~S, is larger than the length of the vector." - new) - (setf (%array-fill-pointer vector) new)) - (error 'simple-type-error - :datum vector - :expected-type '(and vector (satisfies array-has-fill-pointer-p)) - :format-control "~S is not an array with a fill pointer." - :format-arguments (list vector)))) + (flet ((oops (x) + (fill-pointer-error vector x))) + (if (array-has-fill-pointer-p vector) + (if (> new (%array-available-elements vector)) + (oops new) + (setf (%array-fill-pointer vector) new)) + (oops nil)))) ;;; FIXME: It'd probably make sense to use a MACROLET to share the ;;; guts of VECTOR-PUSH between VECTOR-PUSH-EXTEND. Such a macro ;;; should probably be based on the VECTOR-PUSH-EXTEND code (which is ;;; new ca. sbcl-0.7.0) rather than the VECTOR-PUSH code (which dates ;;; back to CMU CL). -(defun vector-push (new-el array) +(defun vector-push (new-element array) #!+sb-doc "Attempt to set the element of ARRAY designated by its fill pointer - to NEW-EL, and increment the fill pointer by one. If the fill pointer is + to NEW-ELEMENT, 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)) nil) (t - (setf (aref array fill-pointer) new-el) + (locally (declare (optimize (safety 0))) + (setf (aref array fill-pointer) new-element)) (setf (%array-fill-pointer array) (1+ fill-pointer)) fill-pointer)))) -(defun vector-push-extend (new-element - vector - &optional - (extension (1+ (length vector)))) - (declare (vector vector) (fixnum extension)) +(defun vector-push-extend (new-element vector &optional min-extension) + (declare (type (or null fixnum) min-extension)) (let ((fill-pointer (fill-pointer vector))) (declare (fixnum fill-pointer)) (when (= fill-pointer (%array-available-elements vector)) - (adjust-array vector (+ fill-pointer extension))) + (let ((min-extension + (or min-extension + (let ((length (length vector))) + (min (1+ length) + (- array-dimension-limit length)))))) + (adjust-array vector (+ fill-pointer (max 1 min-extension))))) ;; disable bounds checking (locally (declare (optimize (safety 0))) (setf (aref vector fill-pointer) new-element)) @@ -830,7 +822,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) @@ -845,18 +836,21 @@ of specialized arrays is supported." ;;;; ADJUST-ARRAY (defun adjust-array (array dimensions &key - (element-type (array-element-type array)) + (element-type (array-element-type array) element-type-p) (initial-element nil initial-element-p) (initial-contents nil initial-contents-p) fill-pointer 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))) (error "The number of dimensions not equal to rank of array.")) - ((not (subtypep element-type (array-element-type array))) + ((and element-type-p + (not (subtypep element-type (array-element-type array)))) (error "The new element type, ~S, is incompatible with old type." element-type)) ((and fill-pointer (not (array-has-fill-pointer-p array))) @@ -871,18 +865,18 @@ of specialized arrays is supported." (cond (initial-contents-p ;; array former contents replaced by INITIAL-CONTENTS (if (or initial-element-p displaced-to) - (error "INITIAL-CONTENTS may not be specified with ~ + (error ":INITIAL-CONTENTS may not be specified with ~ the :INITIAL-ELEMENT or :DISPLACED-TO option.")) (let* ((array-size (apply #'* dimensions)) (array-data (data-vector-from-inits - dimensions array-size element-type + dimensions array-size element-type nil initial-contents initial-contents-p initial-element initial-element-p))) (if (adjustable-array-p array) (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 @@ -909,7 +903,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 @@ -929,9 +923,13 @@ of specialized arrays is supported." (setf new-data (data-vector-from-inits dimensions new-length element-type + (widetag-of old-data) initial-contents initial-contents-p initial-element initial-element-p)) + ;; Provide :END1 to avoid full call to LENGTH + ;; inside REPLACE. (replace new-data old-data + :end1 new-length :start2 old-start :end2 old-end)) (t (setf new-data (shrink-vector old-data new-length)))) @@ -939,7 +937,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)) @@ -953,7 +951,8 @@ of specialized arrays is supported." (> new-length old-length)) (data-vector-from-inits dimensions new-length - element-type () nil + element-type + (widetag-of old-data) () nil initial-element initial-element-p) old-data))) (if (or (zerop old-length) (zerop new-length)) @@ -965,12 +964,12 @@ of specialized arrays is supported." initial-element-p)) (if (adjustable-array-p array) (set-array-header array new-data new-length - new-length 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 - new-length 0 dimensions nil))))))))))) + nil 0 dimensions nil t))))))))))) (defun get-new-fill-pointer (old-array new-array-size fill-pointer) @@ -1050,9 +1049,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 @@ -1069,31 +1135,33 @@ of specialized arrays is supported." (setf (%array-dimension array 0) dimensions)) (setf (%array-displaced-p array) displacedp) array) + +;;; User visible extension +(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. + +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 + ;; the return value is always of the known type. + (truly-the (simple-array * (*)) + (if (array-header-p 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))) -;;;; 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)))) +;;;; ZAP-ARRAY-DATA for ADJUST-ARRAY ;;; 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 @@ -1101,7 +1169,8 @@ of specialized arrays is supported." ;;; 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. @@ -1118,18 +1187,15 @@ of specialized arrays is supported." (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))))) + (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))) + ;; 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 @@ -1268,3 +1334,59 @@ of specialized arrays is supported." (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))))))