X-Git-Url: http://repo.macrolet.net/gitweb/?a=blobdiff_plain;f=src%2Fcompiler%2Fsrctran.lisp;h=369f705c78fbba0bddce7aa476788a1c5e08c162;hb=4a96ec6005851c044a36028c051e8beae82a7155;hp=a49c41502d50ff2055bf0435cb759a988aa94631;hpb=8c1cdfc03a0070295e595e8b0ba97214ccb50a41;p=sbcl.git diff --git a/src/compiler/srctran.lisp b/src/compiler/srctran.lisp index a49c415..369f705 100644 --- a/src/compiler/srctran.lisp +++ b/src/compiler/srctran.lisp @@ -2131,6 +2131,49 @@ (or (null min) (minusp min)))) (values nil t t))) +;;; See _Hacker's Delight_, Henry S. Warren, Jr. pp 58-63 for an +;;; explanation of LOG{AND,IOR,XOR}-DERIVE-UNSIGNED-{LOW,HIGH}-BOUND. +;;; Credit also goes to Raymond Toy for writing (and debugging!) similar +;;; versions in CMUCL, from which these functions copy liberally. + +(defun logand-derive-unsigned-low-bound (x y) + (let ((a (numeric-type-low x)) + (b (numeric-type-high x)) + (c (numeric-type-low y)) + (d (numeric-type-high y))) + (loop for m = (ash 1 (integer-length (lognor a c))) then (ash m -1) + until (zerop m) do + (unless (zerop (logand m (lognot a) (lognot c))) + (let ((temp (logandc2 (logior a m) (1- m)))) + (when (<= temp b) + (setf a temp) + (loop-finish)) + (setf temp (logandc2 (logior c m) (1- m))) + (when (<= temp d) + (setf c temp) + (loop-finish)))) + finally (return (logand a c))))) + +(defun logand-derive-unsigned-high-bound (x y) + (let ((a (numeric-type-low x)) + (b (numeric-type-high x)) + (c (numeric-type-low y)) + (d (numeric-type-high y))) + (loop for m = (ash 1 (integer-length (logxor b d))) then (ash m -1) + until (zerop m) do + (cond + ((not (zerop (logand b (lognot d) m))) + (let ((temp (logior (logandc2 b m) (1- m)))) + (when (>= temp a) + (setf b temp) + (loop-finish)))) + ((not (zerop (logand (lognot b) d m))) + (let ((temp (logior (logandc2 d m) (1- m)))) + (when (>= temp c) + (setf d temp) + (loop-finish))))) + finally (return (logand b d))))) + (defun logand-derive-type-aux (x y &optional same-leaf) (when same-leaf (return-from logand-derive-type-aux x)) @@ -2149,7 +2192,9 @@ ((null y-len) (specifier-type `(unsigned-byte* ,x-len))) (t - (specifier-type `(unsigned-byte* ,(min x-len y-len))))) + (let ((low (logand-derive-unsigned-low-bound x y)) + (high (logand-derive-unsigned-high-bound x y))) + (specifier-type `(integer ,low ,high))))) ;; X is positive, but Y might be negative. (cond ((null x-len) (specifier-type 'unsigned-byte)) @@ -2168,6 +2213,44 @@ ;; We can't tell squat about the result. (specifier-type 'integer))))))) +(defun logior-derive-unsigned-low-bound (x y) + (let ((a (numeric-type-low x)) + (b (numeric-type-high x)) + (c (numeric-type-low y)) + (d (numeric-type-high y))) + (loop for m = (ash 1 (integer-length (logxor a c))) then (ash m -1) + until (zerop m) do + (cond + ((not (zerop (logandc2 (logand c m) a))) + (let ((temp (logand (logior a m) (1+ (lognot m))))) + (when (<= temp b) + (setf a temp) + (loop-finish)))) + ((not (zerop (logandc2 (logand a m) c))) + (let ((temp (logand (logior c m) (1+ (lognot m))))) + (when (<= temp d) + (setf c temp) + (loop-finish))))) + finally (return (logior a c))))) + +(defun logior-derive-unsigned-high-bound (x y) + (let ((a (numeric-type-low x)) + (b (numeric-type-high x)) + (c (numeric-type-low y)) + (d (numeric-type-high y))) + (loop for m = (ash 1 (integer-length (logand b d))) then (ash m -1) + until (zerop m) do + (unless (zerop (logand b d m)) + (let ((temp (logior (- b m) (1- m)))) + (when (>= temp a) + (setf b temp) + (loop-finish)) + (setf temp (logior (- d m) (1- m))) + (when (>= temp c) + (setf d temp) + (loop-finish)))) + finally (return (logior b d))))) + (defun logior-derive-type-aux (x y &optional same-leaf) (when same-leaf (return-from logior-derive-type-aux x)) @@ -2176,9 +2259,11 @@ (cond ((and (not x-neg) (not y-neg)) ;; Both are positive. - (specifier-type `(unsigned-byte* ,(if (and x-len y-len) - (max x-len y-len) - '*)))) + (if (and x-len y-len) + (let ((low (logior-derive-unsigned-low-bound x y)) + (high (logior-derive-unsigned-high-bound x y))) + (specifier-type `(integer ,low ,high))) + (specifier-type `(unsigned-byte* *)))) ((not x-pos) ;; X must be negative. (if (not y-pos) @@ -2208,33 +2293,75 @@ ;; Unbounded. (specifier-type 'integer)))))))) +(defun logxor-derive-unsigned-low-bound (x y) + (let ((a (numeric-type-low x)) + (b (numeric-type-high x)) + (c (numeric-type-low y)) + (d (numeric-type-high y))) + (loop for m = (ash 1 (integer-length (logxor a c))) then (ash m -1) + until (zerop m) do + (cond + ((not (zerop (logandc2 (logand c m) a))) + (let ((temp (logand (logior a m) + (1+ (lognot m))))) + (when (<= temp b) + (setf a temp)))) + ((not (zerop (logandc2 (logand a m) c))) + (let ((temp (logand (logior c m) + (1+ (lognot m))))) + (when (<= temp d) + (setf c temp))))) + finally (return (logxor a c))))) + +(defun logxor-derive-unsigned-high-bound (x y) + (let ((a (numeric-type-low x)) + (b (numeric-type-high x)) + (c (numeric-type-low y)) + (d (numeric-type-high y))) + (loop for m = (ash 1 (integer-length (logand b d))) then (ash m -1) + until (zerop m) do + (unless (zerop (logand b d m)) + (let ((temp (logior (- b m) (1- m)))) + (cond + ((>= temp a) (setf b temp)) + (t (let ((temp (logior (- d m) (1- m)))) + (when (>= temp c) + (setf d temp))))))) + finally (return (logxor b d))))) + (defun logxor-derive-type-aux (x y &optional same-leaf) (when same-leaf (return-from logxor-derive-type-aux (specifier-type '(eql 0)))) (multiple-value-bind (x-len x-pos x-neg) (integer-type-length x) (multiple-value-bind (y-len y-pos y-neg) (integer-type-length y) (cond - ((or (and (not x-neg) (not y-neg)) - (and (not x-pos) (not y-pos))) - ;; Either both are negative or both are positive. The result - ;; will be positive, and as long as the longer. - (specifier-type `(unsigned-byte* ,(if (and x-len y-len) - (max x-len y-len) - '*)))) - ((or (and (not x-pos) (not y-neg)) - (and (not y-pos) (not x-neg))) - ;; Either X is negative and Y is positive or vice-versa. The - ;; result will be negative. - (specifier-type `(integer ,(if (and x-len y-len) - (ash -1 (max x-len y-len)) - '*) - -1))) - ;; We can't tell what the sign of the result is going to be. - ;; All we know is that we don't create new bits. - ((and x-len y-len) - (specifier-type `(signed-byte ,(1+ (max x-len y-len))))) - (t - (specifier-type 'integer)))))) + ((and (not x-neg) (not y-neg)) + ;; Both are positive + (if (and x-len y-len) + (let ((low (logxor-derive-unsigned-low-bound x y)) + (high (logxor-derive-unsigned-high-bound x y))) + (specifier-type `(integer ,low ,high))) + (specifer-type '(unsigned-byte* *)))) + ((and (not x-pos) (not y-pos)) + ;; Both are negative. The result will be positive, and as long + ;; as the longer. + (specifier-type `(unsigned-byte* ,(if (and x-len y-len) + (max x-len y-len) + '*)))) + ((or (and (not x-pos) (not y-neg)) + (and (not y-pos) (not x-neg))) + ;; Either X is negative and Y is positive or vice-versa. The + ;; result will be negative. + (specifier-type `(integer ,(if (and x-len y-len) + (ash -1 (max x-len y-len)) + '*) + -1))) + ;; We can't tell what the sign of the result is going to be. + ;; All we know is that we don't create new bits. + ((and x-len y-len) + (specifier-type `(signed-byte ,(1+ (max x-len y-len))))) + (t + (specifier-type 'integer)))))) (macrolet ((deffrob (logfun) (let ((fun-aux (symbolicate logfun "-DERIVE-TYPE-AUX"))) @@ -2551,6 +2678,16 @@ `(let ((mask (ash (ldb (byte size 0) -1) posn))) (logior (logand new mask) (logand int (lognot mask))))) + +(defoptimizer (mask-signed-field derive-type) ((size x)) + (let ((size (lvar-type size))) + (if (numeric-type-p size) + (let ((size-high (numeric-type-high size))) + (if (and size-high (<= 1 size-high sb!vm:n-word-bits)) + (specifier-type `(signed-byte ,size-high)) + *universal-type*)) + *universal-type*))) + ;;; Modular functions @@ -2559,6 +2696,33 @@ ;;; ;;; and similar for other arguments. +(defun make-modular-fun-type-deriver (prototype class width) + #!-sb-fluid + (binding* ((info (info :function :info prototype) :exit-if-null) + (fun (fun-info-derive-type info) :exit-if-null) + (mask-type (specifier-type + (ecase class + (:unsigned (let ((mask (1- (ash 1 width)))) + `(integer ,mask ,mask))) + (:signed `(signed-byte ,width)))))) + (lambda (call) + (let ((res (funcall fun call))) + (when res + (if (eq class :unsigned) + (logand-derive-type-aux res mask-type)))))) + #!+sb-fluid + (lambda (call) + (binding* ((info (info :function :info prototype) :exit-if-null) + (fun (fun-info-derive-type info) :exit-if-null) + (res (funcall fun call) :exit-if-null) + (mask-type (specifier-type + (ecase class + (:unsigned (let ((mask (1- (ash 1 width)))) + `(integer ,mask ,mask))) + (:signed `(signed-byte ,width)))))) + (if (eq class :unsigned) + (logand-derive-type-aux res mask-type))))) + ;;; Try to recursively cut all uses of LVAR to WIDTH bits. ;;; ;;; For good functions, we just recursively cut arguments; their @@ -2571,54 +2735,59 @@ ;;; modular version, if it exists, or NIL. If we have changed ;;; anything, we need to flush old derived types, because they have ;;; nothing in common with the new code. -(defun cut-to-width (lvar width) +(defun cut-to-width (lvar class width) (declare (type lvar lvar) (type (integer 0) width)) - (labels ((reoptimize-node (node name) - (setf (node-derived-type node) - (fun-type-returns - (info :function :type name))) - (setf (lvar-%derived-type (node-lvar node)) nil) - (setf (node-reoptimize node) t) - (setf (block-reoptimize (node-block node)) t) - (setf (component-reoptimize (node-component node)) t)) - (cut-node (node &aux did-something) - (when (and (not (block-delete-p (node-block node))) - (combination-p node) - (eq (basic-combination-kind node) :known)) - (let* ((fun-ref (lvar-use (combination-fun node))) - (fun-name (leaf-source-name (ref-leaf fun-ref))) - (modular-fun (find-modular-version fun-name width))) - (when (and modular-fun - (not (and (eq fun-name 'logand) - (csubtypep - (single-value-type (node-derived-type node)) - (specifier-type `(unsigned-byte* ,width)))))) - (binding* ((name (etypecase modular-fun - ((eql :good) fun-name) - (modular-fun-info - (modular-fun-info-name modular-fun)) - (function - (funcall modular-fun node width))) - :exit-if-null)) - (unless (eql modular-fun :good) - (setq did-something t) - (change-ref-leaf - fun-ref - (find-free-fun name "in a strange place")) - (setf (combination-kind node) :full)) - (unless (functionp modular-fun) - (dolist (arg (basic-combination-args node)) - (when (cut-lvar arg) - (setq did-something t)))) - (when did-something - (reoptimize-node node name)) - did-something))))) - (cut-lvar (lvar &aux did-something) - (do-uses (node lvar) - (when (cut-node node) - (setq did-something t))) - did-something)) - (cut-lvar lvar))) + (let ((type (specifier-type (if (zerop width) + '(eql 0) + `(,(ecase class (:unsigned 'unsigned-byte) + (:signed 'signed-byte)) + ,width))))) + (labels ((reoptimize-node (node name) + (setf (node-derived-type node) + (fun-type-returns + (info :function :type name))) + (setf (lvar-%derived-type (node-lvar node)) nil) + (setf (node-reoptimize node) t) + (setf (block-reoptimize (node-block node)) t) + (reoptimize-component (node-component node) :maybe)) + (cut-node (node &aux did-something) + (when (and (not (block-delete-p (node-block node))) + (combination-p node) + (eq (basic-combination-kind node) :known)) + (let* ((fun-ref (lvar-use (combination-fun node))) + (fun-name (leaf-source-name (ref-leaf fun-ref))) + (modular-fun (find-modular-version fun-name class width))) + (when (and modular-fun + (not (and (eq fun-name 'logand) + (csubtypep + (single-value-type (node-derived-type node)) + type)))) + (binding* ((name (etypecase modular-fun + ((eql :good) fun-name) + (modular-fun-info + (modular-fun-info-name modular-fun)) + (function + (funcall modular-fun node width))) + :exit-if-null)) + (unless (eql modular-fun :good) + (setq did-something t) + (change-ref-leaf + fun-ref + (find-free-fun name "in a strange place")) + (setf (combination-kind node) :full)) + (unless (functionp modular-fun) + (dolist (arg (basic-combination-args node)) + (when (cut-lvar arg) + (setq did-something t)))) + (when did-something + (reoptimize-node node name)) + did-something))))) + (cut-lvar (lvar &aux did-something) + (do-uses (node lvar) + (when (cut-node node) + (setq did-something t))) + did-something)) + (cut-lvar lvar)))) (defoptimizer (logand optimizer) ((x y) node) (let ((result-type (single-value-type (node-derived-type node)))) @@ -2630,10 +2799,24 @@ (>= low 0)) (let ((width (integer-length high))) (when (some (lambda (x) (<= width x)) - *modular-funs-widths*) + (modular-class-widths *unsigned-modular-class*)) ;; FIXME: This should be (CUT-TO-WIDTH NODE WIDTH). - (cut-to-width x width) - (cut-to-width y width) + (cut-to-width x :unsigned width) + (cut-to-width y :unsigned width) + nil ; After fixing above, replace with T. + ))))))) + +(defoptimizer (mask-signed-field optimizer) ((width x) node) + (let ((result-type (single-value-type (node-derived-type node)))) + (when (numeric-type-p result-type) + (let ((low (numeric-type-low result-type)) + (high (numeric-type-high result-type))) + (when (and (numberp low) (numberp high)) + (let ((width (max (integer-length high) (integer-length low)))) + (when (some (lambda (x) (<= width x)) + (modular-class-widths *signed-modular-class*)) + ;; FIXME: This should be (CUT-TO-WIDTH NODE WIDTH). + (cut-to-width x :signed width) nil ; After fixing above, replace with T. ))))))) @@ -2801,6 +2984,13 @@ (give-up-ir1-transform)) 'x)) +(deftransform mask-signed-field ((size x) ((constant-arg t) *) *) + "fold identity operation" + (let ((size (lvar-value size))) + (unless (csubtypep (lvar-type x) (specifier-type `(signed-byte ,size))) + (give-up-ir1-transform)) + 'x)) + ;;; These are restricted to rationals, because (- 0 0.0) is 0.0, not -0.0, and ;;; (* 0 -4.0) is -0.0. (deftransform - ((x y) ((constant-arg (member 0)) rational) *) @@ -2939,9 +3129,7 @@ ;;;; character operations -(deftransform char-equal ((a b) - ((character-set ((0 . 255))) - (character-set ((0 . 255))))) +(deftransform char-equal ((a b) (base-char base-char)) "open code" '(let* ((ac (char-code a)) (bc (char-code b)) @@ -2953,7 +3141,7 @@ (and (> sum 415) (< sum 461)) (and (> sum 463) (< sum 477)))))))) -(deftransform char-upcase ((x) ((character-set ((0 . 255))))) +(deftransform char-upcase ((x) (base-char)) "open code" '(let ((n-code (char-code x))) (if (or (and (> n-code #o140) ; Octal 141 is #\a. @@ -2965,7 +3153,7 @@ (code-char (logxor #x20 n-code)) x))) -(deftransform char-downcase ((x) ((character-set ((0 . 255))))) +(deftransform char-downcase ((x) (base-char)) "open code" '(let ((n-code (char-code x))) (if (or (and (> n-code 64) ; 65 is #\A. @@ -2996,56 +3184,84 @@ ;;; then the result is definitely false. (deftransform simple-equality-transform ((x y) * * :defun-only t) - (cond ((same-leaf-ref-p x y) - t) - ((not (types-equal-or-intersect (lvar-type x) - (lvar-type y))) + (cond + ((same-leaf-ref-p x y) t) + ((not (types-equal-or-intersect (lvar-type x) (lvar-type y))) nil) - (t - (give-up-ir1-transform)))) + (t (give-up-ir1-transform)))) (macrolet ((def (x) `(%deftransform ',x '(function * *) #'simple-equality-transform))) (def eq) - (def char=) - (def equal)) + (def char=)) -;;; This is similar to SIMPLE-EQUALITY-PREDICATE, except that we also +;;; This is similar to SIMPLE-EQUALITY-TRANSFORM, except that we also ;;; try to convert to a type-specific predicate or EQ: ;;; -- If both args are characters, convert to CHAR=. This is better than ;;; just converting to EQ, since CHAR= may have special compilation ;;; strategies for non-standard representations, etc. -;;; -- If either arg is definitely not a number, then we can compare -;;; with EQ. +;;; -- If either arg is definitely a fixnum we punt and let the backend +;;; deal with it. +;;; -- If either arg is definitely not a number or a fixnum, then we +;;; can compare with EQ. ;;; -- Otherwise, we try to put the arg we know more about second. If X ;;; is constant then we put it second. If X is a subtype of Y, we put ;;; it second. These rules make it easier for the back end to match ;;; these interesting cases. -;;; -- If Y is a fixnum, then we quietly pass because the back end can -;;; handle that case, otherwise give an efficiency note. (deftransform eql ((x y) * *) "convert to simpler equality predicate" (let ((x-type (lvar-type x)) (y-type (lvar-type y)) - (char-type (specifier-type 'character)) - (number-type (specifier-type 'number))) - (cond ((same-leaf-ref-p x y) - t) - ((not (types-equal-or-intersect x-type y-type)) - nil) - ((and (csubtypep x-type char-type) - (csubtypep y-type char-type)) - '(char= x y)) - ((or (not (types-equal-or-intersect x-type number-type)) - (not (types-equal-or-intersect y-type number-type))) - '(eq x y)) - ((and (not (constant-lvar-p y)) - (or (constant-lvar-p x) - (and (csubtypep x-type y-type) - (not (csubtypep y-type x-type))))) - '(eql y x)) - (t - (give-up-ir1-transform))))) + (char-type (specifier-type 'character))) + (flet ((simple-type-p (type) + (csubtypep type (specifier-type '(or fixnum (not number))))) + (fixnum-type-p (type) + (csubtypep type (specifier-type 'fixnum)))) + (cond + ((same-leaf-ref-p x y) t) + ((not (types-equal-or-intersect x-type y-type)) + nil) + ((and (csubtypep x-type char-type) + (csubtypep y-type char-type)) + '(char= x y)) + ((or (fixnum-type-p x-type) (fixnum-type-p y-type)) + (give-up-ir1-transform)) + ((or (simple-type-p x-type) (simple-type-p y-type)) + '(eq x y)) + ((and (not (constant-lvar-p y)) + (or (constant-lvar-p x) + (and (csubtypep x-type y-type) + (not (csubtypep y-type x-type))))) + '(eql y x)) + (t + (give-up-ir1-transform)))))) + +;;; similarly to the EQL transform above, we attempt to constant-fold +;;; or convert to a simpler predicate: mostly we have to be careful +;;; with strings and bit-vectors. +(deftransform equal ((x y) * *) + "convert to simpler equality predicate" + (let ((x-type (lvar-type x)) + (y-type (lvar-type y)) + (string-type (specifier-type 'string)) + (bit-vector-type (specifier-type 'bit-vector))) + (cond + ((same-leaf-ref-p x y) t) + ((and (csubtypep x-type string-type) + (csubtypep y-type string-type)) + '(string= x y)) + ((and (csubtypep x-type bit-vector-type) + (csubtypep y-type bit-vector-type)) + '(bit-vector-= x y)) + ;; if at least one is not a string, and at least one is not a + ;; bit-vector, then we can reason from types. + ((and (not (and (types-equal-or-intersect x-type string-type) + (types-equal-or-intersect y-type string-type))) + (not (and (types-equal-or-intersect x-type bit-vector-type) + (types-equal-or-intersect y-type bit-vector-type))) + (not (types-equal-or-intersect x-type y-type))) + nil) + (t (give-up-ir1-transform))))) ;;; Convert to EQL if both args are rational and complexp is specified ;;; and the same for both.