X-Git-Url: http://repo.macrolet.net/gitweb/?a=blobdiff_plain;f=src%2Fcompiler%2Fsrctran.lisp;h=e13c30e019e7799ab08cf50a3f42b4620e683ba5;hb=1daa58cfa315fe86634069c941cf54ec8f95623c;hp=298c8a6b8e8e6ae8a6615d5a5045e1ab84c697e1;hpb=423b1f8cba83d16e57e852a51cf5d51ef709b2ed;p=sbcl.git diff --git a/src/compiler/srctran.lisp b/src/compiler/srctran.lisp index 298c8a6..e13c30e 100644 --- a/src/compiler/srctran.lisp +++ b/src/compiler/srctran.lisp @@ -134,6 +134,11 @@ (1 `(cons ,(first args) nil)) (t (values nil t)))) +(defoptimizer (list derive-type) ((&rest args) node) + (if args + (specifier-type 'cons) + (specifier-type 'null))) + ;;; And similarly for LIST*. (define-source-transform list* (arg &rest others) (cond ((not others) arg) @@ -145,6 +150,63 @@ (specifier-type 'cons) (lvar-type arg))) +;;; + +(define-source-transform nconc (&rest args) + (case (length args) + (0 ()) + (1 (car args)) + (t (values nil t)))) + +;;; (append nil nil nil fixnum) => fixnum +;;; (append x x cons x x) => cons +;;; (append x x x x list) => list +;;; (append x x x x sequence) => sequence +;;; (append fixnum x ...) => nil +(defun derive-append-type (args) + (when (null args) + (return-from derive-append-type (specifier-type 'null))) + (let* ((cons-type (specifier-type 'cons)) + (null-type (specifier-type 'null)) + (list-type (specifier-type 'list)) + (last (lvar-type (car (last args))))) + ;; Derive the actual return type, assuming that all but the last + ;; arguments are LISTs (otherwise, APPEND/NCONC doesn't return). + (loop with all-nil = t ; all but the last args are NIL? + with some-cons = nil ; some args are conses? + for (arg next) on args + for lvar-type = (type-approx-intersection2 (lvar-type arg) + list-type) + while next + do (multiple-value-bind (typep definitely) + (ctypep nil lvar-type) + (cond ((type= lvar-type *empty-type*) + ;; type mismatch! insert an inline check that'll cause + ;; compile-time warnings. + (assert-lvar-type arg list-type + (lexenv-policy *lexenv*))) + (some-cons) ; we know result's a cons -- nothing to do + ((and (not typep) definitely) ; can't be NIL + (setf some-cons t)) ; must be a CONS + (all-nil + (setf all-nil (csubtypep lvar-type null-type))))) + finally + ;; if some of the previous arguments are CONSes so is the result; + ;; if all the previous values are NIL, we're a fancy identity; + ;; otherwise, could be either + (return (cond (some-cons cons-type) + (all-nil last) + (t (type-union last cons-type))))))) + +(defoptimizer (append derive-type) ((&rest args)) + (derive-append-type args)) + +(defoptimizer (sb!impl::append2 derive-type) ((&rest args)) + (derive-append-type args)) + +(defoptimizer (nconc derive-type) ((&rest args)) + (derive-append-type args)) + ;;; Translate RPLACx to LET and SETF. (define-source-transform rplaca (x y) (once-only ((n-x x)) @@ -236,8 +298,24 @@ ;;; on the argument types), but we make it a regular transform so that ;;; the VM has a chance to see the bare LOGTEST and potentiall choose ;;; to implement it differently. --njf, 06-02-2006 -(deftransform logtest ((x y) * *) - `(not (zerop (logand x y)))) +;;; +;;; Other transforms may be useful even with direct LOGTEST VOPs; let +;;; them fire (including the type-directed constant folding below), but +;;; disable the inlining rewrite in such cases. -- PK, 2013-05-20 +(deftransform logtest ((x y) * * :node node) + (let ((type (two-arg-derive-type x y + #'logand-derive-type-aux + #'logand))) + (multiple-value-bind (typep definitely) + (ctypep 0 type) + (cond ((and (not typep) definitely) + t) + ((type= type (specifier-type '(eql 0))) + nil) + ((neq :default (combination-implementation-style node)) + (give-up-ir1-transform)) + (t + `(not (zerop (logand x y)))))))) (deftransform logbitp ((index integer) (unsigned-byte (or (signed-byte #.sb!vm:n-word-bits) @@ -2686,7 +2764,98 @@ (specifier-type `(signed-byte ,size-high)) *universal-type*)) *universal-type*))) + +;;; Rightward ASH +#!+ash-right-vops +(progn + (defun %ash/right (integer amount) + (ash integer (- amount))) + + (deftransform ash ((integer amount)) + "Convert ASH of signed word to %ASH/RIGHT" + (unless (and (csubtypep (lvar-type integer) ; do that ourselves to avoid + (specifier-type 'sb!vm:signed-word)) ; optimization + (csubtypep (lvar-type amount) ; notes. + (specifier-type '(integer * 0)))) + (give-up-ir1-transform)) + (when (constant-lvar-p amount) + (give-up-ir1-transform)) + (let ((use (lvar-uses amount))) + (cond ((and (combination-p use) + (eql '%negate (lvar-fun-name (combination-fun use)))) + (splice-fun-args amount '%negate 1) + `(lambda (integer amount) + (declare (type unsigned-byte amount)) + (%ash/right integer (if (>= amount ,sb!vm:n-word-bits) + ,(1- sb!vm:n-word-bits) + amount)))) + (t + `(%ash/right integer (if (<= amount ,(- sb!vm:n-word-bits)) + ,(1- sb!vm:n-word-bits) + (- amount))))))) + + (deftransform ash ((integer amount)) + "Convert ASH of word to %ASH/RIGHT" + (unless (and (csubtypep (lvar-type integer) + (specifier-type 'sb!vm:word)) + (csubtypep (lvar-type amount) + (specifier-type '(integer * 0)))) + (give-up-ir1-transform)) + (when (constant-lvar-p amount) + (give-up-ir1-transform)) + (let ((use (lvar-uses amount))) + (cond ((and (combination-p use) + (eql '%negate (lvar-fun-name (combination-fun use)))) + (splice-fun-args amount '%negate 1) + `(lambda (integer amount) + (declare (type unsigned-byte amount)) + (if (>= amount ,sb!vm:n-word-bits) + 0 + (%ash/right integer amount)))) + (t + `(if (<= amount ,(- sb!vm:n-word-bits)) + 0 + (%ash/right integer (- amount))))))) + + (deftransform %ash/right ((integer amount) (integer (constant-arg unsigned-byte))) + "Convert %ASH/RIGHT by constant back to ASH" + `(ash integer ,(- (lvar-value amount)))) + + (deftransform %ash/right ((integer amount) * * :node node) + "strength reduce large variable right shift" + (let ((return-type (single-value-type (node-derived-type node)))) + (cond ((type= return-type (specifier-type '(eql 0))) + 0) + ((type= return-type (specifier-type '(eql -1))) + -1) + ((csubtypep return-type (specifier-type '(member -1 0))) + `(ash integer ,(- sb!vm:n-word-bits))) + (t + (give-up-ir1-transform))))) + (defun %ash/right-derive-type-aux (n-type shift same-arg) + (declare (ignore same-arg)) + (or (and (or (csubtypep n-type (specifier-type 'sb!vm:signed-word)) + (csubtypep n-type (specifier-type 'word))) + (csubtypep shift (specifier-type `(mod ,sb!vm:n-word-bits))) + (let ((n-low (numeric-type-low n-type)) + (n-high (numeric-type-high n-type)) + (s-low (numeric-type-low shift)) + (s-high (numeric-type-high shift))) + (make-numeric-type :class 'integer :complexp :real + :low (when n-low + (if (minusp n-low) + (ash n-low (- s-low)) + (ash n-low (- s-high)))) + :high (when n-high + (if (minusp n-high) + (ash n-high (- s-high)) + (ash n-high (- s-low))))))) + *universal-type*)) + + (defoptimizer (%ash/right derive-type) ((n shift)) + (two-arg-derive-type n shift #'%ash/right-derive-type-aux #'%ash/right)) + ) ;;; Modular functions @@ -2751,58 +2920,121 @@ (setf (node-reoptimize node) t) (setf (block-reoptimize (node-block node)) t) (reoptimize-component (node-component node) :maybe)) + (insert-lvar-cut (lvar) + "Insert a LOGAND/MASK-SIGNED-FIELD to cut the value of LVAR + to the required bit width. Returns T if any change was made. + + When the destination of LVAR will definitely cut LVAR's value + to width (i.e. it's a logand or mask-signed-field with constant + other argument), do nothing. Otherwise, splice LOGAND/M-S-F in." + (binding* ((dest (lvar-dest lvar) :exit-if-null) + (nil (combination-p dest) :exit-if-null) + (name (lvar-fun-name (combination-fun dest) t)) + (args (combination-args dest))) + (case name + (logand + (when (= 2 (length args)) + (let ((other (if (eql (first args) lvar) + (second args) + (first args)))) + (when (and (constant-lvar-p other) + (ctypep (lvar-value other) type) + (not signedp)) + (return-from insert-lvar-cut))))) + (mask-signed-field + (when (and signedp + (eql lvar (second args)) + (constant-lvar-p (first args)) + (<= (lvar-value (first args)) width)) + (return-from insert-lvar-cut))))) + (filter-lvar lvar + (if signedp + `(mask-signed-field ,width 'dummy) + `(logand 'dummy ,(ldb (byte width 0) -1)))) + (do-uses (node lvar) + (setf (block-reoptimize (node-block node)) t) + (reoptimize-component (node-component node) :maybe)) + t) (cut-node (node &aux did-something) - (when (and (not (block-delete-p (node-block node))) - (ref-p node) - (constant-p (ref-leaf node))) - (let* ((constant-value (constant-value (ref-leaf node))) - (new-value (if signedp - (mask-signed-field width constant-value) - (ldb (byte width 0) constant-value)))) - (unless (= constant-value new-value) - (change-ref-leaf node (make-constant new-value)) - (let ((lvar (node-lvar node))) - (setf (lvar-%derived-type lvar) - (and (lvar-has-single-use-p lvar) - (make-values-type :required (list (ctype-of new-value)))))) - (setf (block-reoptimize (node-block node)) t) - (reoptimize-component (node-component node) :maybe) - (return-from cut-node t)))) - (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 kind signedp 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) + "Try to cut a node to width. The primary return value is + whether we managed to cut (cleverly), and the second whether + anything was changed." + (when (block-delete-p (node-block node)) + (return-from cut-node (values t nil))) + (typecase node + (ref + (typecase (ref-leaf node) + (constant + (let* ((constant-value (constant-value (ref-leaf node))) + (new-value (if signedp + (mask-signed-field width constant-value) + (ldb (byte width 0) constant-value)))) + (cond ((= constant-value new-value) + (values t nil)) ; we knew what to do and did nothing + (t + (change-ref-leaf node (make-constant new-value) + :recklessly t) + (let ((lvar (node-lvar node))) + (setf (lvar-%derived-type lvar) + (and (lvar-has-single-use-p lvar) + (make-values-type :required (list (ctype-of new-value)))))) + (setf (block-reoptimize (node-block node)) t) + (reoptimize-component (node-component node) :maybe) + (values t t))))))) + (combination + (when (eq (basic-combination-kind node) :known) + (let* ((fun-ref (lvar-use (combination-fun node))) + (fun-name (lvar-fun-name (combination-fun node))) + (modular-fun (find-modular-version fun-name kind + signedp 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)) + (values t did-something)))))))) + (cut-lvar (lvar &aux did-something must-insert) + "Cut all the LVAR's use nodes. If any of them wasn't handled + and its type is too wide for the operation we wish to perform + insert an explicit bit-width narrowing operation (LOGAND or + MASK-SIGNED-FIELD) between the LVAR (*) and its destination. + The narrowing operation might not be inserted if the LVAR's + destination is already such an operation, to avoid endless + recursion. + + (*) We can't easily do that for each node, and doing so might + result in code bloat, anyway. (I'm also not sure it would be + correct for complicated C/D FG)" (do-uses (node lvar) - (when (cut-node node) - (setq did-something t))) + (multiple-value-bind (handled any-change) + (cut-node node) + (setf did-something (or did-something any-change) + must-insert (or must-insert + (not (or handled + (csubtypep (single-value-type + (node-derived-type node)) + type))))))) + (when must-insert + (setf did-something (or (insert-lvar-cut lvar) did-something))) did-something)) (cut-lvar lvar)))) @@ -2830,53 +3062,85 @@ (return-from best-modular-version (values (car ugt) :untagged (cdr ugt)))))))) +(defun integer-type-numeric-bounds (type) + (typecase type + (numeric-type (values (numeric-type-low type) + (numeric-type-high type))) + (union-type + (let ((low nil) + (high nil)) + (dolist (type (union-type-types type) (values low high)) + (unless (and (numeric-type-p type) + (eql (numeric-type-class type) 'integer)) + (return (values nil nil))) + (let ((this-low (numeric-type-low type)) + (this-high (numeric-type-high type))) + (setf low (min this-low (or low this-low)) + high (max this-high (or high this-high))))))))) + (defoptimizer (logand optimizer) ((x y) 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) - (>= low 0)) - (let ((width (integer-length high))) - (multiple-value-bind (w kind signedp) - (best-modular-version width nil) - (when w - ;; FIXME: This should be (CUT-TO-WIDTH NODE KIND WIDTH SIGNEDP). - ;; - ;; FIXME: I think the FIXME (which is from APD) above - ;; implies that CUT-TO-WIDTH should do /everything/ - ;; that's required, including reoptimizing things - ;; itself that it knows are necessary. At the moment, - ;; CUT-TO-WIDTH sets up some new calls with - ;; combination-type :FULL, which later get noticed as - ;; known functions and properly converted. - ;; - ;; We cut to W not WIDTH if SIGNEDP is true, because - ;; signed constant replacement needs to know which bit - ;; in the field is the signed bit. - (let ((xact (cut-to-width x kind (if signedp w width) signedp)) - (yact (cut-to-width y kind (if signedp w width) signedp))) - (declare (ignore xact yact)) - nil) ; After fixing above, replace with T, meaning - ; "don't reoptimize this (LOGAND) node any more". - )))))))) + (multiple-value-bind (low high) + (integer-type-numeric-bounds result-type) + (when (and (numberp low) + (numberp high) + (>= low 0)) + (let ((width (integer-length high))) + (multiple-value-bind (w kind signedp) + (best-modular-version width nil) + (when w + ;; FIXME: This should be (CUT-TO-WIDTH NODE KIND WIDTH SIGNEDP). + ;; + ;; FIXME: I think the FIXME (which is from APD) above + ;; implies that CUT-TO-WIDTH should do /everything/ + ;; that's required, including reoptimizing things + ;; itself that it knows are necessary. At the moment, + ;; CUT-TO-WIDTH sets up some new calls with + ;; combination-type :FULL, which later get noticed as + ;; known functions and properly converted. + ;; + ;; We cut to W not WIDTH if SIGNEDP is true, because + ;; signed constant replacement needs to know which bit + ;; in the field is the signed bit. + (let ((xact (cut-to-width x kind (if signedp w width) signedp)) + (yact (cut-to-width y kind (if signedp w width) signedp))) + (declare (ignore xact yact)) + nil) ; After fixing above, replace with T, meaning + ; "don't reoptimize this (LOGAND) node any more". + ))))))) (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)))) - (multiple-value-bind (w kind) - (best-modular-version (1+ width) t) - (when w - ;; FIXME: This should be (CUT-TO-WIDTH NODE KIND W T). - ;; [ see comment above in LOGAND optimizer ] - (cut-to-width x kind w t) - nil ; After fixing above, replace with T. - )))))))) + (multiple-value-bind (low high) + (integer-type-numeric-bounds result-type) + (when (and (numberp low) (numberp high)) + (let ((width (max (integer-length high) (integer-length low)))) + (multiple-value-bind (w kind) + (best-modular-version (1+ width) t) + (when w + ;; FIXME: This should be (CUT-TO-WIDTH NODE KIND W T). + ;; [ see comment above in LOGAND optimizer ] + (cut-to-width x kind w t) + nil ; After fixing above, replace with T. + ))))))) + +(defoptimizer (logior optimizer) ((x y) node) + (let ((result-type (single-value-type (node-derived-type node)))) + (multiple-value-bind (low high) + (integer-type-numeric-bounds result-type) + (when (and (numberp low) + (numberp high) + (<= high 0)) + (let ((width (integer-length low))) + (multiple-value-bind (w kind) + (best-modular-version (1+ width) t) + (when w + ;; FIXME: see comment in LOGAND optimizer + (let ((xact (cut-to-width x kind w t)) + (yact (cut-to-width y kind w t))) + (declare (ignore xact yact)) + nil) ; After fixing above, replace with T + ))))))) ;;; miscellanous numeric transforms @@ -2885,11 +3149,11 @@ (if (and (constant-lvar-p x) (not (constant-lvar-p y))) `(,(lvar-fun-name (basic-combination-fun node)) - y + (truly-the ,(lvar-type y) y) ,(lvar-value x)) (give-up-ir1-transform))) -(dolist (x '(= char= + * logior logand logxor)) +(dolist (x '(= char= + * logior logand logxor logtest)) (%deftransform x '(function * *) #'commutative-arg-swap "place constant arg last")) @@ -3147,14 +3411,17 @@ (def logxor -1 (lognot x)) (def logxor 0 x)) +(defun least-zero-bit (x) + (and (/= x -1) + (1- (integer-length (logxor x (1+ x)))))) + (deftransform logand ((x y) (* (constant-arg t)) *) "fold identity operation" - (let ((y (lvar-value y))) - (unless (and (plusp y) - (= y (1- (ash 1 (integer-length y))))) - (give-up-ir1-transform)) - (unless (csubtypep (lvar-type x) - (specifier-type `(integer 0 ,y))) + (let* ((y (lvar-value y)) + (width (or (least-zero-bit y) '*))) + (unless (and (neq width 0) ; (logand x 0) handled elsewhere + (csubtypep (lvar-type x) + (specifier-type `(unsigned-byte ,width)))) (give-up-ir1-transform)) 'x)) @@ -3165,6 +3432,74 @@ (give-up-ir1-transform)) 'x)) +(deftransform logior ((x y) (* (constant-arg t)) *) + "fold identity operation" + (let* ((y (lvar-value y)) + (width (or (least-zero-bit (lognot y)) + (give-up-ir1-transform)))) ; (logior x 0) handled elsewhere + (unless (csubtypep (lvar-type x) + (specifier-type `(integer ,(- (ash 1 width)) -1))) + (give-up-ir1-transform)) + 'x)) + +;;; Pick off easy association opportunities for constant folding. +;;; More complicated stuff that also depends on commutativity +;;; (e.g. (f (f x k1) (f y k2)) => (f (f x y) (f k1 k2))) should +;;; probably be handled with a more general tree-rewriting pass. +(macrolet ((def (operator &key (type 'integer) (folded operator)) + `(deftransform ,operator ((x z) (,type (constant-arg ,type))) + ,(format nil "associate ~A/~A of constants" + operator folded) + (binding* ((node (if (lvar-has-single-use-p x) + (lvar-use x) + (give-up-ir1-transform))) + (nil (or (and (combination-p node) + (eq (lvar-fun-name + (combination-fun node)) + ',folded)) + (give-up-ir1-transform))) + (y (second (combination-args node))) + (nil (or (constant-lvar-p y) + (give-up-ir1-transform))) + (y (lvar-value y))) + (unless (typep y ',type) + (give-up-ir1-transform)) + (splice-fun-args x ',folded 2) + `(lambda (x y z) + (declare (ignore y z)) + ;; (operator (folded x y) z) + ;; == (operator x (folded z y)) + (,',operator x ',(,folded (lvar-value z) y))))))) + (def logand) + (def logior) + (def logxor) + (def logtest :folded logand) + (def + :type rational) + (def + :type rational :folded -) + (def * :type rational) + (def * :type rational :folded /)) + +(deftransform mask-signed-field ((width x) ((constant-arg unsigned-byte) *)) + "Fold mask-signed-field/mask-signed-field of constant width" + (binding* ((node (if (lvar-has-single-use-p x) + (lvar-use x) + (give-up-ir1-transform))) + (nil (or (combination-p node) + (give-up-ir1-transform))) + (nil (or (eq (lvar-fun-name (combination-fun node)) + 'mask-signed-field) + (give-up-ir1-transform))) + (x-width (first (combination-args node))) + (nil (or (constant-lvar-p x-width) + (give-up-ir1-transform))) + (x-width (lvar-value x-width))) + (unless (typep x-width 'unsigned-byte) + (give-up-ir1-transform)) + (splice-fun-args x 'mask-signed-field 2) + `(lambda (width x-width x) + (declare (ignore width x-width)) + (mask-signed-field ,(min (lvar-value width) x-width) 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) *) @@ -3174,6 +3509,25 @@ "convert (* x 0) to 0" 0) +(deftransform %negate ((x) (rational)) + "Eliminate %negate/%negate of rationals" + (splice-fun-args x '%negate 1) + '(the rational x)) + +(deftransform %negate ((x) (number)) + "Combine %negate/*" + (let ((use (lvar-uses x)) + arg) + (unless (and (combination-p use) + (eql '* (lvar-fun-name (combination-fun use))) + (constant-lvar-p (setf arg (second (combination-args use)))) + (numberp (setf arg (lvar-value arg)))) + (give-up-ir1-transform)) + (splice-fun-args x '* 2) + `(lambda (x y) + (declare (ignore y)) + (* x ,(- arg))))) + ;;; Return T if in an arithmetic op including lvars X and Y, the ;;; result type is not affected by the type of X. That is, Y is at ;;; least as contagious as X. @@ -3416,10 +3770,10 @@ ((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)) - (commutative-arg-swap node)) ((or (eq-comparable-type-p x-type) (eq-comparable-type-p y-type)) - '(eq x y)) + (if (and (constant-lvar-p x) (not (constant-lvar-p y))) + '(eq y x) + '(eq x y))) ((and (not (constant-lvar-p y)) (or (constant-lvar-p x) (and (csubtypep x-type y-type) @@ -4384,3 +4738,35 @@ (policy-quality-name-p (lvar-value quality-name))) (give-up-ir1-transform)) '(%policy-quality policy quality-name)) + +(deftransform encode-universal-time + ((second minute hour date month year &optional time-zone) + ((constant-arg (mod 60)) (constant-arg (mod 60)) + (constant-arg (mod 24)) + (constant-arg (integer 1 31)) + (constant-arg (integer 1 12)) + (constant-arg (integer 1899)) + (constant-arg (rational -24 24)))) + (let ((second (lvar-value second)) + (minute (lvar-value minute)) + (hour (lvar-value hour)) + (date (lvar-value date)) + (month (lvar-value month)) + (year (lvar-value year)) + (time-zone (lvar-value time-zone))) + (if (zerop (rem time-zone 1/3600)) + (encode-universal-time second minute hour date month year time-zone) + (give-up-ir1-transform)))) + +#!-(and win32 (not sb-thread)) +(deftransform sleep ((seconds) ((integer 0 #.(expt 10 8)))) + `(sb!unix:nanosleep seconds 0)) + +#!-(and win32 (not sb-thread)) +(deftransform sleep ((seconds) ((constant-arg (real 0)))) + (let ((seconds-value (lvar-value seconds))) + (multiple-value-bind (seconds nano) + (sb!impl::split-seconds-for-sleep seconds-value) + (if (> seconds (expt 10 8)) + (give-up-ir1-transform) + `(sb!unix:nanosleep ,seconds ,nano)))))