;;;; -*- coding: utf-8; -*-
changes in sbcl-1.0.13 relative to sbcl-1.0.12:
+ * bug fix: some sequence functions elided bounds checking when
+ SPEED > SAFETY.
* bug fix: too liberal weakening of union-type checks when SPEED >
SAFETY.
* bug fix: more bogus fixnum declarations in ROOM implementation
#+sbcl
;; respect the fill pointer
(let ((end (or end (length sequence))))
- (sb-kernel:with-array-data ((data sequence) (real-start start) (real-end end))
+ (sb-kernel:with-array-data ((data sequence)
+ (real-start start)
+ (real-end end)
+ :check-fill-pointer t)
(declare (ignore real-end))
(update-md5-state state data :start real-start
:end (+ real-start (- end start)))))
"%SINH" "%SQRT" "%SXHASH-SIMPLE-STRING"
"%SXHASH-SIMPLE-SUBSTRING" "%TAN" "%TAN-QUICK" "%TANH"
"%UNARY-ROUND" "%UNARY-TRUNCATE" "%UNARY-FTRUNCATE"
- "%WITH-ARRAY-DATA" "%WITH-ARRAY-DATA-MACRO"
+ "%WITH-ARRAY-DATA"
+ "%WITH-ARRAY-DATA/FP"
+ "%WITH-ARRAY-DATA-MACRO"
"*CURRENT-LEVEL-IN-PRINT*"
"*EMPTY-TYPE*" "*GC-INHIBIT*" "*GC-PENDING*"
#!+sb-thread "*STOP-FOR-GC-PENDING*"
"EFFECTIVE-FIND-POSITION-TEST"
"EFFECTIVE-FIND-POSITION-KEY" "ERROR-NUMBER-OR-LOSE"
"EXTENDED-CHAR-P"
- "FAILED-%WITH-ARRAY-DATA" "FDEFINITION-OBJECT"
+ "FDEFINITION-OBJECT"
"FDOCUMENTATION" "FILENAME"
"FIND-AND-INIT-OR-CHECK-LAYOUT"
"FIND-DEFSTRUCT-DESCRIPTION"
(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)
(assert (typep array '(simple-array * (*))))
(values array start end 0))
+(defun sb!kernel:%with-array-data/fp (array start end)
+ (assert (typep array '(simple-array * (*))))
+ (values array start end 0))
+
(defun sb!kernel:signed-byte-32-p (number)
(typep number '(signed-byte 32)))
(declare (type (vector (unsigned-byte 8)) vector))
(with-array-data ((vector vector)
(start start)
- (end (%check-vector-sequence-bounds vector start end)))
+ (end end)
+ :check-fill-pointer t)
(declare (type (simple-array (unsigned-byte 8) (*)) vector))
(funcall (symbol-function (first (external-formats-funs external-format)))
vector start end)))
(declare (type string string))
(with-array-data ((string string)
(start start)
- (end (%check-vector-sequence-bounds string start end)))
+ (end end)
+ :check-fill-pointer t)
(declare (type simple-string string))
(funcall (symbol-function (second (external-formats-funs external-format)))
string start end (if null-terminate 1 0))))
;; this for now. [noted by anonymous long ago] -- WHN 19991130
`(or (char= ,char #\\)
(char= ,char #\"))))
- (with-array-data ((data string) (start) (end (length string)))
+ (with-array-data ((data string) (start) (end)
+ :check-fill-pointer t)
(do ((index start (1+ index)))
((>= index end))
(let ((char (schar data index)))
(declare (string string))
(with-array-data ((string string :offset-var offset)
(start start)
- (end (%check-vector-sequence-bounds string start end)))
+ (end end)
+ :check-fill-pointer t)
(let ((stream (make-string-input-stream string start end)))
(values (if preserve-whitespace
(read-preserving-whitespace stream eof-error-p eof-value)
:format-arguments (list string))))
(with-array-data ((string string :offset-var offset)
(start start)
- (end (%check-vector-sequence-bounds string start end)))
+ (end end)
+ :check-fill-pointer t)
(let ((index (do ((i start (1+ i)))
((= i end)
(if junk-allowed
(frob sequence-arg from-end)
(with-array-data ((sequence sequence-arg :offset-var offset)
(start start)
- (end (%check-vector-sequence-bounds
- sequence-arg start end)))
+ (end end)
+ :check-fill-pointer t)
(multiple-value-bind (f p)
(macrolet ((frob2 () '(if from-end
(frob sequence t)
(if key (%coerce-callable-to-fun key) #'identity))
(let ((key-fun-or-nil (and key (%coerce-callable-to-fun key))))
(with-array-data ((vector (the vector sequence))
- (start 0)
- (end (length sequence)))
+ (start)
+ (end)
+ :check-fill-pointer t)
(sort-vector vector start end predicate-fun key-fun-or-nil))
sequence)
(apply #'sb!sequence:sort sequence predicate args))))
(declare (type string string))
(declare (type ansi-stream stream))
(declare (type index start end))
- (if (array-header-p string)
- (with-array-data ((data string) (offset-start start)
- (offset-end end))
- (funcall (ansi-stream-sout stream)
- stream data offset-start offset-end))
- (funcall (ansi-stream-sout stream) stream string start end))
+ (with-array-data ((data string) (offset-start start)
+ (offset-end end)
+ :check-fill-pointer t)
+ (funcall (ansi-stream-sout stream)
+ stream data offset-start offset-end))
string)
(defun %write-string (string stream start end)
(declare (type string string)
(type index start)
(type (or index null) end))
- (let* ((string (coerce string '(simple-array character (*))))
- (end (%check-vector-sequence-bounds string start end)))
+ (let* ((string (coerce string '(simple-array character (*)))))
+ ;; FIXME: Why WITH-ARRAY-DATA, since the array is already simple?
(with-array-data ((string string) (start start) (end end))
(internal-make-string-input-stream
string ;; now simple
(return i))
(setf (first rem) el)))))
(vector
- (with-array-data ((data seq) (offset-start start) (offset-end end))
+ (with-array-data ((data seq) (offset-start start) (offset-end end)
+ :check-fill-pointer t)
(if (compatible-vector-and-stream-element-types-p data stream)
(let* ((numbytes (- end start))
(bytes-read (read-n-bytes stream data offset-start
(string
(%write-string seq stream start end))
(vector
- (with-array-data ((data seq) (offset-start start) (offset-end end))
+ (with-array-data ((data seq) (offset-start start) (offset-end end)
+ :check-fill-pointer t)
(labels
((output-seq-in-loop ()
(let ((write-function
`(let* ((,string (if (stringp ,string) ,string (string ,string))))
(with-array-data ((,string ,string)
(,start ,start)
- (,end
- (%check-vector-sequence-bounds ,string ,start ,end)))
+ (,end ,end)
+ :check-fill-pointer t)
,@forms)))
;;; WITH-STRING is like WITH-ONE-STRING, but doesn't parse keywords.
(sb!xc:defmacro with-string (string &rest forms)
`(let ((,string (if (stringp ,string) ,string (string ,string))))
(with-array-data ((,string ,string)
(start)
- (end (length (the vector ,string))))
+ (end)
+ :check-fill-pointer t)
,@forms)))
;;; WITH-TWO-STRINGS is used to set up string comparison operations. The
;;; keywords are parsed, and the strings are hacked into SIMPLE-STRINGs.
(,string2 (if (stringp ,string2) ,string2 (string ,string2))))
(with-array-data ((,string1 ,string1 :offset-var ,cum-offset-1)
(,start1 ,start1)
- (,end1 (%check-vector-sequence-bounds
- ,string1 ,start1 ,end1)))
+ (,end1 ,end1)
+ :check-fill-pointer t)
(with-array-data ((,string2 ,string2)
(,start2 ,start2)
- (,end2 (%check-vector-sequence-bounds
- ,string2 ,start2 ,end2)))
+ (,end2 ,end2)
+ :check-fill-pointer t)
,@forms))))
) ; EVAL-WHEN
(aref heap 0)))
(defun heap-extract (heap i &key (key #'identity) (test #'>=))
- (when (< (length heap) i)
+ (unless (> (length heap) i)
(error "Heap underflow"))
(prog1
(aref heap i)
;;; Figure out the type of the data vector if we know the argument
;;; element type.
-(defoptimizer (%with-array-data derive-type) ((array start end))
+(defun derive-%with-array-data/mumble-type (array)
(let ((atype (lvar-type array)))
(when (array-type-p atype)
(specifier-type
`(simple-array ,(type-specifier
- (array-type-specialized-element-type atype))
- (*))))))
+ (array-type-specialized-element-type atype))
+ (*))))))
+(defoptimizer (%with-array-data derive-type) ((array start end))
+ (derive-%with-array-data/mumble-type array))
+(defoptimizer (%with-array-data/fp derive-type) ((array start end))
+ (derive-%with-array-data/mumble-type array))
(defoptimizer (array-row-major-index derive-type) ((array &rest indices))
(assert-array-rank array (length indices))
(give-up-ir1-transform))
(t
(let ((dim (lvar-value dimension)))
+ ;; FIXME: Can SPEED > SAFETY weaken this check to INTEGER?
`(the (integer 0 (,dim)) index)))))
\f
;;;; WITH-ARRAY-DATA
+(defun bounding-index-error (array start end)
+ (let ((size (array-total-size array)))
+ (error 'bounding-indices-bad-error
+ :datum (cons start end)
+ :expected-type `(cons (integer 0 ,size)
+ (integer ,start ,size))
+ :object array)))
+
+(defun bounding-index-error/fp (array start end)
+ (let ((size (length array)))
+ (error 'bounding-indices-bad-error
+ :datum (cons start end)
+ :expected-type `(cons (integer 0 ,size)
+ (integer ,start ,size))
+ :object array)))
+
;;; This checks to see whether the array is simple and the start and
;;; end are in bounds. If so, it proceeds with those values.
;;; Otherwise, it calls %WITH-ARRAY-DATA. Note that %WITH-ARRAY-DATA
(def!macro with-array-data (((data-var array &key offset-var)
(start-var &optional (svalue 0))
(end-var &optional (evalue nil))
- &key force-inline)
- &body forms)
+ &key force-inline check-fill-pointer)
+ &body forms
+ &environment env)
(once-only ((n-array array)
(n-svalue `(the index ,svalue))
(n-evalue `(the (or index null) ,evalue)))
- `(multiple-value-bind (,data-var
- ,start-var
- ,end-var
- ,@(when offset-var `(,offset-var)))
- (if (not (array-header-p ,n-array))
- (let ((,n-array ,n-array))
- (declare (type (simple-array * (*)) ,n-array))
- ,(once-only ((n-len `(length ,n-array))
- (n-end `(or ,n-evalue ,n-len)))
- `(if (<= ,n-svalue ,n-end ,n-len)
- ;; success
- (values ,n-array ,n-svalue ,n-end 0)
- (failed-%with-array-data ,n-array
- ,n-svalue
- ,n-evalue))))
- (,(if force-inline '%with-array-data-macro '%with-array-data)
- ,n-array ,n-svalue ,n-evalue))
- ,@forms)))
+ (let ((check-bounds (policy env (= 0 insert-array-bounds-checks))))
+ `(multiple-value-bind (,data-var
+ ,start-var
+ ,end-var
+ ,@(when offset-var `(,offset-var)))
+ (if (not (array-header-p ,n-array))
+ (let ((,n-array ,n-array))
+ (declare (type (simple-array * (*)) ,n-array))
+ ,(once-only ((n-len (if check-fill-pointer
+ `(length ,n-array)
+ `(array-total-size ,n-array)))
+ (n-end `(or ,n-evalue ,n-len)))
+ (if check-bounds
+ `(values ,n-array ,n-svalue ,n-end 0)
+ `(if (<= ,n-svalue ,n-end ,n-len)
+ (values ,n-array ,n-svalue ,n-end 0)
+ ,(if check-fill-pointer
+ `(bounding-index-error/fp ,n-array ,n-svalue ,n-evalue)
+ `(bounding-index-error ,n-array ,n-svalue ,n-evalue))))))
+ ,(if force-inline
+ `(%with-array-data-macro ,n-array ,n-svalue ,n-evalue
+ :check-bounds ,check-bounds
+ :check-fill-pointer ,check-fill-pointer)
+ (if check-fill-pointer
+ `(%with-array-data/fp ,n-array ,n-svalue ,n-evalue)
+ `(%with-array-data ,n-array ,n-svalue ,n-evalue))))
+ ,@forms))))
;;; This is the fundamental definition of %WITH-ARRAY-DATA, for use in
;;; DEFTRANSFORMs and DEFUNs.
end
&key
(element-type '*)
- unsafe?
- fail-inline?)
+ check-bounds
+ check-fill-pointer)
(with-unique-names (size defaulted-end data cumulative-offset)
- `(let* ((,size (array-total-size ,array))
- (,defaulted-end
- (cond (,end
- (unless (or ,unsafe? (<= ,end ,size))
- ,(if fail-inline?
- `(error 'bounding-indices-bad-error
- :datum (cons ,start ,end)
- :expected-type `(cons (integer 0 ,',size)
- (integer ,',start ,',size))
- :object ,array)
- `(failed-%with-array-data ,array ,start ,end)))
- ,end)
- (t ,size))))
- (unless (or ,unsafe? (<= ,start ,defaulted-end))
- ,(if fail-inline?
- `(error 'bounding-indices-bad-error
- :datum (cons ,start ,end)
- :expected-type `(cons (integer 0 ,',size)
- (integer ,',start ,',size))
- :object ,array)
- `(failed-%with-array-data ,array ,start ,end)))
+ `(let* ((,size ,(if check-fill-pointer
+ `(length ,array)
+ `(array-total-size ,array)))
+ (,defaulted-end (or ,end ,size)))
+ ,@(when check-bounds
+ `((unless (<= ,start ,defaulted-end ,size)
+ ,(if check-fill-pointer
+ `(bounding-index-error/fp ,array ,start ,end)
+ `(bounding-index-error ,array ,start ,end)))))
(do ((,data ,array (%array-data-vector ,data))
(,cumulative-offset 0
(+ ,cumulative-offset
(the index ,cumulative-offset)))
(declare (type index ,cumulative-offset))))))
-(deftransform %with-array-data ((array start end)
- ;; It might very well be reasonable to
- ;; allow general ARRAY here, I just
- ;; haven't tried to understand the
- ;; performance issues involved. --
- ;; WHN, and also CSR 2002-05-26
- ((or vector simple-array) index (or index null))
- *
- :node node
- :policy (> speed space))
- "inline non-SIMPLE-vector-handling logic"
+(defun transform-%with-array-data/muble (array node check-fill-pointer)
(let ((element-type (upgraded-element-type-specifier-or-give-up array))
(type (lvar-type array)))
(if (and (array-type-p type)
(listp (array-type-dimensions type))
(not (null (cdr (array-type-dimensions type)))))
- ;; If it's a simple multidimensional array, then just return its
- ;; data vector directly rather than going through
- ;; %WITH-ARRAY-DATA-MACRO. SBCL doesn't generally generate code
- ;; that would use this currently, but we have encouraged users
- ;; to use WITH-ARRAY-DATA and we may use it ourselves at some
- ;; point in the future for optimized libraries or similar.
+ ;; If it's a simple multidimensional array, then just return
+ ;; its data vector directly rather than going through
+ ;; %WITH-ARRAY-DATA-MACRO. SBCL doesn't generally generate
+ ;; code that would use this currently, but we have encouraged
+ ;; users to use WITH-ARRAY-DATA and we may use it ourselves at
+ ;; some point in the future for optimized libraries or
+ ;; similar.
+ ;;
+ ;; FIXME: The return values here don't seem sane, and
+ ;; bounds-checks are elided!
`(let ((data (truly-the (simple-array ,element-type (*))
(%array-data-vector array))))
(values data 0 (length data) 0))
`(%with-array-data-macro array start end
- :unsafe? ,(policy node (= safety 0))
+ :check-fill-pointer ,check-fill-pointer
+ :check-bounds ,(policy node (< 0 insert-array-bounds-checks))
:element-type ,element-type))))
+
+;; It might very well be reasonable to allow general ARRAY here, I
+;; just haven't tried to understand the performance issues involved.
+;; -- WHN, and also CSR 2002-05-26
+(deftransform %with-array-data ((array start end)
+ ((or vector simple-array) index (or index null) t)
+ *
+ :node node
+ :policy (> speed space))
+ "inline non-SIMPLE-vector-handling logic"
+ (transform-%with-array-data/muble array node nil))
+(deftransform %with-array-data/fp ((array start end)
+ ((or vector simple-array) index (or index null) t)
+ *
+ :node node
+ :policy (> speed space))
+ "inline non-SIMPLE-vector-handling logic"
+ (transform-%with-array-data/muble array node t))
\f
;;;; array accessors
(defknown %with-array-data (array index (or index null))
(values (simple-array * (*)) index index index)
(foldable flushable))
+(defknown %with-array-data/fp (array index (or index null))
+ (values (simple-array * (*)) index index index)
+ (foldable flushable))
(defknown %set-symbol-package (symbol t) t (unsafe))
(defknown %coerce-name-to-fun ((or symbol cons)) function (flushable))
(defknown %coerce-callable-to-fun (callable) function (flushable))
-(defknown failed-%with-array-data (t t t) nil)
+(defknown bounding-index-error (t t t) nil)
+(defknown bounding-index-error/fp (t t t) nil)
(defknown %find-position
(t sequence t index sequence-end function function)
(values t (or index null))
(deftransform %check-vector-sequence-bounds ((vector start end)
(vector * *) *
:node node)
- ;; FIXME: Should this not be INSERT-ARRAY-BOUNDS-CHECKS?
- (if (policy node (< safety speed))
+ (if (policy node (= 0 insert-array-bounds-checks))
'(or end (length vector))
'(let ((length (length vector)))
- (if (<= 0 start (or end length) length)
- (or end length)
- (sb!impl::signal-bounding-indices-bad-error vector start end)))))
+ (if (<= 0 start (or end length) length)
+ (or end length)
+ (sb!impl::signal-bounding-indices-bad-error vector start end)))))
(defun specialized-list-seek-function-name (function-name key-functions)
(or (find-symbol (with-output-to-string (s)
(values
`(with-array-data ((data seq)
(start start)
- (end end))
+ (end end)
+ :check-fill-pointer t)
(declare (type (simple-array ,element-type 1) data))
(declare (type fixnum start end))
(do ((i start (1+ i)))
end-arg
element
done-p-expr)
- (with-unique-names (offset block index n-sequence sequence n-end end)
- `(let ((,n-sequence ,sequence-arg)
- (,n-end ,end-arg))
+ (with-unique-names (offset block index n-sequence sequence end)
+ `(let* ((,n-sequence ,sequence-arg))
(with-array-data ((,sequence ,n-sequence :offset-var ,offset)
(,start ,start)
- (,end (%check-vector-sequence-bounds
- ,n-sequence ,start ,n-end)))
+ (,end ,end-arg)
+ :check-fill-pointer t)
(block ,block
(macrolet ((maybe-return ()
;; WITH-ARRAY-DATA has already performed bounds
;; in the inner loop.
'(let ((,element (locally (declare (optimize (insert-array-bounds-checks 0)))
(aref ,sequence ,index))))
- (when ,done-p-expr
- (return-from ,block
- (values ,element
- (- ,index ,offset)))))))
+ (when ,done-p-expr
+ (return-from ,block
+ (values ,element
+ (- ,index ,offset)))))))
(if ,from-end
(loop for ,index
;; (If we aren't fastidious about declaring that
from (1- ,end) downto ,start do
(maybe-return))
(loop for ,index of-type index from ,start below ,end do
- (maybe-return))))
+ (maybe-return))))
(values nil nil))))))
(def!macro %find-position-vector-macro (item sequence
"expand inline"
(check-inlineability-of-find-position-if sequence from-end)
'(%find-position-vector-macro item sequence
- from-end start end key test))
+ from-end start end key test))
;;; logic to unravel :TEST, :TEST-NOT, and :KEY options in FIND,
;;; POSITION-IF, etc.
(svref x 0))
(assert (raises-error? (svrefalike #*0) type-error))
\f
-;;; checks for uniform bounding index handling under SAFETY 3 code.
+;;; checks for uniform bounding index handling.
+;;;
+;;; This used to be SAFETY 3 only, but bypassing these checks with
+;;; above-zero speed when SPEED > SAFETY is not The SBCL Way.
;;;
;;; KLUDGE: not all in one big form because that causes SBCL to spend
;;; an absolute age trying to compile it.
(defmacro sequence-bounding-indices-test (&body body)
`(progn
- (locally
+ (locally
;; See Issues 332 [and 333(!)] in the CLHS
- (declare (optimize (safety 3)))
+ (declare (optimize (speed 3) (safety 1)))
(let ((string (make-array 10
:fill-pointer 5
:initial-element #\a
,@(cdr body))))
(locally
;; See Issues 332 [and 333(!)] in the CLHS
- (declare (optimize (safety 3)))
+ (declare (optimize (speed 3) (safety 1)))
(let ((string (make-array 10
:fill-pointer 5
:initial-element #\a
;;; checkins which aren't released. (And occasionally for internal
;;; versions, especially for internal versions off the main CVS
;;; branch, it gets hairier, e.g. "0.pre7.14.flaky4.13".)
-"1.0.12.4"
+"1.0.12.5"