Implement suggestions of Paul Khuong re. POPCNT
[sbcl.git] / src / compiler / generic / vm-tran.lisp
blobd3b0461826e1521eb888c618ebd07e386c598050
1 ;;;; implementation-dependent transforms
3 ;;;; This software is part of the SBCL system. See the README file for
4 ;;;; more information.
5 ;;;;
6 ;;;; This software is derived from the CMU CL system, which was
7 ;;;; written at Carnegie Mellon University and released into the
8 ;;;; public domain. The software is in the public domain and is
9 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
10 ;;;; files for more information.
12 (in-package "SB!C")
14 ;;; We need to define these predicates, since the TYPEP source
15 ;;; transform picks whichever predicate was defined last when there
16 ;;; are multiple predicates for equivalent types.
17 (define-source-transform short-float-p (x) `(single-float-p ,x))
18 #!-long-float
19 (define-source-transform long-float-p (x) `(double-float-p ,x))
21 (define-source-transform compiled-function-p (x)
22 #!-sb-eval
23 `(functionp ,x)
24 #!+sb-eval
25 (once-only ((x x))
26 `(and (functionp ,x)
27 (not (sb!eval:interpreted-function-p ,x)))))
29 (define-source-transform char-int (x)
30 `(char-code ,x))
32 (deftransform abs ((x) (rational))
33 '(if (< x 0) (- x) x))
35 ;;; We don't want to clutter the bignum code.
36 #!+(or x86 x86-64)
37 (define-source-transform sb!bignum:%bignum-ref (bignum index)
38 ;; KLUDGE: We use TRULY-THE here because even though the bignum code
39 ;; is (currently) compiled with (SAFETY 0), the compiler insists on
40 ;; inserting CAST nodes to ensure that INDEX is of the correct type.
41 ;; These CAST nodes do not generate any type checks, but they do
42 ;; interfere with the operation of FOLD-INDEX-ADDRESSING, below.
43 ;; This scenario is a problem for the more user-visible case of
44 ;; folding as well. --njf, 2006-12-01
45 `(sb!bignum:%bignum-ref-with-offset ,bignum
46 (truly-the bignum-index ,index) 0))
48 #!+(or x86 x86-64)
49 (defun fold-index-addressing (fun-name element-size lowtag data-offset
50 index offset &optional setter-p)
51 (multiple-value-bind (func index-args) (extract-fun-args index '(+ -) 2)
52 (destructuring-bind (x constant) index-args
53 (unless (and (constant-lvar-p constant)
54 ;; we lose if the remaining argument isn't a fixnum
55 (csubtypep (lvar-type x) (specifier-type 'fixnum)))
56 (give-up-ir1-transform))
57 (let ((value (lvar-value constant))
58 new-offset)
59 (unless (and (integerp value)
60 (sb!vm::foldable-constant-offset-p
61 element-size lowtag data-offset
62 (setf new-offset (funcall func (lvar-value offset)
63 value))))
64 (give-up-ir1-transform "constant is too large for inlining"))
65 (splice-fun-args index func 2)
66 `(lambda (thing index off1 off2 ,@(when setter-p
67 '(value)))
68 (declare (ignore off1 off2))
69 (,fun-name thing index ',new-offset ,@(when setter-p
70 '(value))))))))
72 #!+(or x86 x86-64)
73 (deftransform sb!bignum:%bignum-ref-with-offset
74 ((bignum index offset) * * :node node)
75 (fold-index-addressing 'sb!bignum:%bignum-ref-with-offset
76 sb!vm:n-word-bits sb!vm:other-pointer-lowtag
77 sb!vm:bignum-digits-offset
78 index offset))
80 ;;; The layout is stored in slot 0.
81 (define-source-transform %instance-layout (x)
82 `(truly-the layout (%instance-ref ,x 0)))
83 (define-source-transform %set-instance-layout (x val)
84 `(%instance-set ,x 0 (the layout ,val)))
85 (define-source-transform %funcallable-instance-layout (x)
86 `(truly-the layout (%funcallable-instance-info ,x 0)))
87 (define-source-transform %set-funcallable-instance-layout (x val)
88 `(setf (%funcallable-instance-info ,x 0) (the layout ,val)))
90 ;;;; simplifying HAIRY-DATA-VECTOR-REF and HAIRY-DATA-VECTOR-SET
92 (deftransform hairy-data-vector-ref ((string index) (simple-string t))
93 (let ((ctype (lvar-type string)))
94 (if (array-type-p ctype)
95 ;; the other transform will kick in, so that's OK
96 (give-up-ir1-transform)
97 `(etypecase string
98 ((simple-array character (*))
99 (data-vector-ref string index))
100 #!+sb-unicode
101 ((simple-array base-char (*))
102 (data-vector-ref string index))
103 ((simple-array nil (*))
104 (data-nil-vector-ref string index))))))
106 ;;; This and the corresponding -SET transform work equally well on non-simple
107 ;;; arrays, but after benchmarking (on x86), Nikodemus didn't find any cases
108 ;;; where it actually helped with non-simple arrays -- to the contrary, it
109 ;;; only made for bigger and up to 100% slower code.
110 (deftransform hairy-data-vector-ref ((array index) (simple-array t) *)
111 "avoid runtime dispatch on array element type"
112 (let* ((type (lvar-type array))
113 (element-ctype (array-type-upgraded-element-type type))
114 (declared-element-ctype (array-type-declared-element-type type)))
115 (declare (type ctype element-ctype))
116 (when (eq *wild-type* element-ctype)
117 (give-up-ir1-transform
118 "Upgraded element type of array is not known at compile time."))
119 ;; (The expansion here is basically a degenerate case of
120 ;; WITH-ARRAY-DATA. Since WITH-ARRAY-DATA is implemented as a
121 ;; macro, and macros aren't expanded in transform output, we have
122 ;; to hand-expand it ourselves.)
123 (let* ((element-type-specifier (type-specifier element-ctype)))
124 `(multiple-value-bind (array index)
125 (%data-vector-and-index array index)
126 (declare (type (simple-array ,element-type-specifier 1) array))
127 ,(let ((bare-form '(data-vector-ref array index)))
128 (cond ((eql element-ctype *empty-type*)
129 `(data-nil-vector-ref array index))
130 ((type= element-ctype declared-element-ctype)
131 bare-form)
133 `(the ,(type-specifier declared-element-ctype)
134 ,bare-form))))))))
136 ;;; Transform multi-dimensional array to one dimensional data vector
137 ;;; access.
138 (deftransform data-vector-ref ((array index) (simple-array t))
139 (let ((array-type (lvar-type array)))
140 (unless (array-type-p array-type)
141 (give-up-ir1-transform))
142 (let ((dims (array-type-dimensions array-type)))
143 (when (or (atom dims) (= (length dims) 1))
144 (give-up-ir1-transform))
145 (let ((el-type (array-type-specialized-element-type array-type))
146 (total-size (if (member '* dims)
148 (reduce #'* dims))))
149 `(data-vector-ref (truly-the (simple-array ,(type-specifier el-type)
150 (,total-size))
151 (%array-data-vector array))
152 index)))))
154 ;;; Transform data vector access to a form that opens up optimization
155 ;;; opportunities. On platforms that support DATA-VECTOR-REF-WITH-OFFSET
156 ;;; DATA-VECTOR-REF is not supported at all.
157 #!+(or x86 x86-64)
158 (define-source-transform data-vector-ref (array index)
159 `(data-vector-ref-with-offset ,array ,index 0))
161 #!+(or x86 x86-64)
162 (deftransform data-vector-ref-with-offset ((array index offset))
163 (let ((array-type (lvar-type array)))
164 (when (or (not (array-type-p array-type))
165 (eql (array-type-specialized-element-type array-type)
166 *wild-type*))
167 (give-up-ir1-transform))
168 ;; It shouldn't be possible to get here with anything but a non-complex
169 ;; vector.
170 (aver (not (array-type-complexp array-type)))
171 (let* ((element-type (type-specifier (array-type-specialized-element-type array-type)))
172 (saetp (find-saetp element-type)))
173 (when (< (sb!vm:saetp-n-bits saetp) sb!vm:n-byte-bits)
174 (give-up-ir1-transform))
175 (fold-index-addressing 'data-vector-ref-with-offset
176 (sb!vm:saetp-n-bits saetp)
177 sb!vm:other-pointer-lowtag
178 sb!vm:vector-data-offset
179 index offset))))
181 (deftransform hairy-data-vector-set ((string index new-value)
182 (simple-string t t))
183 (let ((ctype (lvar-type string)))
184 (if (array-type-p ctype)
185 ;; the other transform will kick in, so that's OK
186 (give-up-ir1-transform)
187 `(etypecase string
188 ((simple-array character (*))
189 (data-vector-set string index new-value))
190 #!+sb-unicode
191 ((simple-array base-char (*))
192 (data-vector-set string index new-value))
193 ((simple-array nil (*))
194 (data-vector-set string index new-value))))))
196 ;;; This and the corresponding -REF transform work equally well on non-simple
197 ;;; arrays, but after benchmarking (on x86), Nikodemus didn't find any cases
198 ;;; where it actually helped with non-simple arrays -- to the contrary, it
199 ;;; only made for bigger and up 1o 100% slower code.
200 (deftransform hairy-data-vector-set ((array index new-value)
201 (simple-array t t)
203 "avoid runtime dispatch on array element type"
204 (let* ((type (lvar-type array))
205 (element-ctype (array-type-upgraded-element-type type))
206 (declared-element-ctype (array-type-declared-element-type type)))
207 (declare (type ctype element-ctype))
208 (when (eq *wild-type* element-ctype)
209 (give-up-ir1-transform
210 "Upgraded element type of array is not known at compile time."))
211 (let ((element-type-specifier (type-specifier element-ctype)))
212 `(multiple-value-bind (array index)
213 (%data-vector-and-index array index)
214 (declare (type (simple-array ,element-type-specifier 1) array)
215 (type ,element-type-specifier new-value))
216 ,(if (type= element-ctype declared-element-ctype)
217 '(data-vector-set array index new-value)
218 `(truly-the ,(type-specifier declared-element-ctype)
219 (data-vector-set array index
220 (the ,(type-specifier declared-element-ctype)
221 new-value))))))))
223 ;;; Transform multi-dimensional array to one dimensional data vector
224 ;;; access.
225 (deftransform data-vector-set ((array index new-value)
226 (simple-array t t))
227 (let ((array-type (lvar-type array)))
228 (unless (array-type-p array-type)
229 (give-up-ir1-transform))
230 (let ((dims (array-type-dimensions array-type)))
231 (when (or (atom dims) (= (length dims) 1))
232 (give-up-ir1-transform))
233 (let ((el-type (array-type-specialized-element-type array-type))
234 (total-size (if (member '* dims)
236 (reduce #'* dims))))
237 `(data-vector-set (truly-the (simple-array ,(type-specifier el-type)
238 (,total-size))
239 (%array-data-vector array))
240 index
241 new-value)))))
243 ;;; Transform data vector access to a form that opens up optimization
244 ;;; opportunities.
245 #!+(or x86 x86-64)
246 (define-source-transform data-vector-set (array index new-value)
247 `(data-vector-set-with-offset ,array ,index 0 ,new-value))
249 #!+(or x86 x86-64)
250 (deftransform data-vector-set-with-offset ((array index offset new-value))
251 (let ((array-type (lvar-type array)))
252 (when (or (not (array-type-p array-type))
253 (eql (array-type-specialized-element-type array-type)
254 *wild-type*))
255 ;; We don't yet know the exact element type, but will get that
256 ;; knowledge after some more type propagation.
257 (give-up-ir1-transform))
258 (aver (not (array-type-complexp array-type)))
259 (let* ((element-type (type-specifier (array-type-specialized-element-type array-type)))
260 (saetp (find-saetp element-type)))
261 (when (< (sb!vm:saetp-n-bits saetp) sb!vm:n-byte-bits)
262 (give-up-ir1-transform))
263 (fold-index-addressing 'data-vector-set-with-offset
264 (sb!vm:saetp-n-bits saetp)
265 sb!vm:other-pointer-lowtag
266 sb!vm:vector-data-offset
267 index offset t))))
269 (defun maybe-array-data-vector-type-specifier (array-lvar)
270 (let ((atype (lvar-type array-lvar)))
271 (when (array-type-p atype)
272 (let ((dims (array-type-dimensions atype)))
273 (if (or (array-type-complexp atype)
274 (eq '* dims)
275 (notevery #'integerp dims))
276 `(simple-array ,(type-specifier
277 (array-type-specialized-element-type atype))
278 (*))
279 `(simple-array ,(type-specifier
280 (array-type-specialized-element-type atype))
281 (,(apply #'* dims))))))))
283 (macrolet ((def (name)
284 `(defoptimizer (,name derive-type) ((array-lvar))
285 (let ((spec (maybe-array-data-vector-type-specifier array-lvar)))
286 (when spec
287 (specifier-type spec))))))
288 (def %array-data-vector)
289 (def array-storage-vector))
291 (defoptimizer (%data-vector-and-index derive-type) ((array index))
292 (declare (ignore index))
293 (let ((spec (maybe-array-data-vector-type-specifier array)))
294 (when spec
295 (values-specifier-type `(values ,spec index)))))
297 (deftransform %data-vector-and-index ((%array %index)
298 (simple-array t)
300 ;; KLUDGE: why the percent signs? Well, ARRAY and INDEX are
301 ;; respectively exported from the CL and SB!INT packages, which
302 ;; means that they're visible to all sorts of things. If the
303 ;; compiler can prove that the call to ARRAY-HEADER-P, below, either
304 ;; returns T or NIL, it will delete the irrelevant branch. However,
305 ;; user code might have got here with a variable named CL:ARRAY, and
306 ;; quite often compiler code with a variable named SB!INT:INDEX, so
307 ;; this can generate code deletion notes for innocuous user code:
308 ;; (DEFUN F (ARRAY I) (DECLARE (SIMPLE-VECTOR ARRAY)) (AREF ARRAY I))
309 ;; -- CSR, 2003-04-01
311 ;; We do this solely for the -OR-GIVE-UP side effect, since we want
312 ;; to know that the type can be figured out in the end before we
313 ;; proceed, but we don't care yet what the type will turn out to be.
314 (upgraded-element-type-specifier-or-give-up %array)
316 '(if (array-header-p %array)
317 (values (%array-data-vector %array) %index)
318 (values %array %index)))
320 ;;;; BIT-VECTOR hackery
322 ;;; SIMPLE-BIT-VECTOR bit-array operations are transformed to a word
323 ;;; loop that does 32 bits at a time.
325 ;;; FIXME: This is a lot of repeatedly macroexpanded code. It should
326 ;;; be a function call instead.
327 (macrolet ((def (bitfun wordfun)
328 `(deftransform ,bitfun ((bit-array-1 bit-array-2 result-bit-array)
329 (simple-bit-vector
330 simple-bit-vector
331 simple-bit-vector)
333 :node node :policy (>= speed space))
334 `(progn
335 ,@(unless (policy node (zerop safety))
336 '((unless (= (length bit-array-1)
337 (length bit-array-2)
338 (length result-bit-array))
339 (error "Argument and/or result bit arrays are not the same length:~
340 ~% ~S~% ~S ~% ~S"
341 bit-array-1
342 bit-array-2
343 result-bit-array))))
344 (let ((length (length result-bit-array)))
345 (if (= length 0)
346 ;; We avoid doing anything to 0-length
347 ;; bit-vectors, or rather, the memory that
348 ;; follows them. Other divisible-by-32 cases
349 ;; are handled by the (1- length), below.
350 ;; CSR, 2002-04-24
351 result-bit-array
352 (do ((index 0 (1+ index))
353 ;; bit-vectors of length 1-32 need
354 ;; precisely one (SETF %VECTOR-RAW-BITS),
355 ;; done here in the epilogue. - CSR,
356 ;; 2002-04-24
357 (end-1 (truncate (truly-the index (1- length))
358 sb!vm:n-word-bits)))
359 ((>= index end-1)
360 (setf (%vector-raw-bits result-bit-array index)
361 (,',wordfun (%vector-raw-bits bit-array-1 index)
362 (%vector-raw-bits bit-array-2 index)))
363 result-bit-array)
364 (declare (optimize (speed 3) (safety 0))
365 (type index index end-1))
366 (setf (%vector-raw-bits result-bit-array index)
367 (,',wordfun (%vector-raw-bits bit-array-1 index)
368 (%vector-raw-bits bit-array-2 index))))))))))
369 (def bit-and word-logical-and)
370 (def bit-ior word-logical-or)
371 (def bit-xor word-logical-xor)
372 (def bit-eqv word-logical-eqv)
373 (def bit-nand word-logical-nand)
374 (def bit-nor word-logical-nor)
375 (def bit-andc1 word-logical-andc1)
376 (def bit-andc2 word-logical-andc2)
377 (def bit-orc1 word-logical-orc1)
378 (def bit-orc2 word-logical-orc2))
380 (deftransform bit-not
381 ((bit-array result-bit-array)
382 (simple-bit-vector simple-bit-vector) *
383 :node node :policy (>= speed space))
384 `(progn
385 ,@(unless (policy node (zerop safety))
386 '((unless (= (length bit-array)
387 (length result-bit-array))
388 (error "Argument and result bit arrays are not the same length:~
389 ~% ~S~% ~S"
390 bit-array result-bit-array))))
391 (let ((length (length result-bit-array)))
392 (if (= length 0)
393 ;; We avoid doing anything to 0-length bit-vectors, or rather,
394 ;; the memory that follows them. Other divisible-by
395 ;; n-word-bits cases are handled by the (1- length), below.
396 ;; CSR, 2002-04-24
397 result-bit-array
398 (do ((index 0 (1+ index))
399 ;; bit-vectors of length 1 to n-word-bits need precisely
400 ;; one (SETF %VECTOR-RAW-BITS), done here in the
401 ;; epilogue. - CSR, 2002-04-24
402 (end-1 (truncate (truly-the index (1- length))
403 sb!vm:n-word-bits)))
404 ((>= index end-1)
405 (setf (%vector-raw-bits result-bit-array index)
406 (word-logical-not (%vector-raw-bits bit-array index)))
407 result-bit-array)
408 (declare (optimize (speed 3) (safety 0))
409 (type index index end-1))
410 (setf (%vector-raw-bits result-bit-array index)
411 (word-logical-not (%vector-raw-bits bit-array index))))))))
413 (deftransform bit-vector-= ((x y) (simple-bit-vector simple-bit-vector))
414 `(and (= (length x) (length y))
415 (let ((length (length x)))
416 (or (= length 0)
417 (do* ((i 0 (+ i 1))
418 (end-1 (floor (1- length) sb!vm:n-word-bits)))
419 ((>= i end-1)
420 (let* ((extra (1+ (mod (1- length) sb!vm:n-word-bits)))
421 (mask (ash #.(1- (ash 1 sb!vm:n-word-bits))
422 (- extra sb!vm:n-word-bits)))
423 (numx
424 (logand
425 (ash mask
426 ,(ecase sb!c:*backend-byte-order*
427 (:little-endian 0)
428 (:big-endian
429 '(- sb!vm:n-word-bits extra))))
430 (%vector-raw-bits x i)))
431 (numy
432 (logand
433 (ash mask
434 ,(ecase sb!c:*backend-byte-order*
435 (:little-endian 0)
436 (:big-endian
437 '(- sb!vm:n-word-bits extra))))
438 (%vector-raw-bits y i))))
439 (declare (type (integer 1 #.sb!vm:n-word-bits) extra)
440 (type sb!vm:word mask numx numy))
441 (= numx numy)))
442 (declare (type index i end-1))
443 (let ((numx (%vector-raw-bits x i))
444 (numy (%vector-raw-bits y i)))
445 (declare (type sb!vm:word numx numy))
446 (unless (= numx numy)
447 (return nil))))))))
449 (deftransform count ((item sequence) (bit simple-bit-vector) *
450 :policy (>= speed space))
451 `(let ((length (length sequence)))
452 (if (zerop length)
454 (do ((index 0 (1+ index))
455 (count 0)
456 (end-1 (truncate (truly-the index (1- length))
457 sb!vm:n-word-bits)))
458 ((>= index end-1)
459 ;; "(mod (1- length) ...)" is the bit index within the word
460 ;; of the array index of the ultimate bit to be examined.
461 ;; "1+" it is the number of bits in that word.
462 ;; But I don't get why people are allowed to store random data that
463 ;; we mask off, as if we could accomodate all possible ways that
464 ;; unsafe code can spew bits where they don't belong.
465 ;; Does it have to do with %shrink-vector, perhaps?
466 ;; Some rationale would be nice...
467 (let* ((extra (1+ (mod (1- length) sb!vm:n-word-bits)))
468 (mask (ash #.(1- (ash 1 sb!vm:n-word-bits))
469 (- extra sb!vm:n-word-bits)))
470 ;; The above notwithstanding, for big-endian wouldn't it
471 ;; be possible to write this expression as a single shift?
472 ;; (LOGAND MOST-POSITIVE-WORD (ASH most-positive-word (- n-word-bits extra)))
473 ;; rather than a right-shift to fill in zeros on the left
474 ;; then by a left-shift to left-align the 1s?
475 (bits (logand (ash mask
476 ,(ecase sb!c:*backend-byte-order*
477 (:little-endian 0)
478 (:big-endian
479 '(- sb!vm:n-word-bits extra))))
480 (%vector-raw-bits sequence index))))
481 (declare (type (integer 1 #.sb!vm:n-word-bits) extra))
482 (declare (type sb!vm:word mask bits))
483 (incf count (logcount bits))
484 ,(if (constant-lvar-p item)
485 (if (zerop (lvar-value item))
486 '(- length count)
487 'count)
488 '(if (zerop item)
489 (- length count)
490 count))))
491 (declare (type index index count end-1)
492 (optimize (speed 3) (safety 0)))
493 (incf count (logcount (%vector-raw-bits sequence index)))))))
495 (deftransform fill ((sequence item) (simple-bit-vector bit) *
496 :policy (>= speed space))
497 (let ((value (if (constant-lvar-p item)
498 (if (= (lvar-value item) 0)
500 #.(1- (ash 1 sb!vm:n-word-bits)))
501 `(if (= item 0) 0 #.(1- (ash 1 sb!vm:n-word-bits))))))
502 `(let ((length (length sequence))
503 (value ,value))
504 (if (= length 0)
505 sequence
506 (do ((index 0 (1+ index))
507 ;; bit-vectors of length 1 to n-word-bits need precisely
508 ;; one (SETF %VECTOR-RAW-BITS), done here in the
509 ;; epilogue. - CSR, 2002-04-24
510 (end-1 (truncate (truly-the index (1- length))
511 sb!vm:n-word-bits)))
512 ((>= index end-1)
513 (setf (%vector-raw-bits sequence index) value)
514 sequence)
515 (declare (optimize (speed 3) (safety 0))
516 (type index index end-1))
517 (setf (%vector-raw-bits sequence index) value))))))
519 (deftransform fill ((sequence item) (simple-base-string base-char) *
520 :policy (>= speed space))
521 (let ((value (if (constant-lvar-p item)
522 (let* ((char (lvar-value item))
523 (code (sb!xc:char-code char))
524 (accum 0))
525 (dotimes (i sb!vm:n-word-bytes accum)
526 (setf accum (logior accum (ash code (* 8 i))))))
527 `(let ((code (sb!xc:char-code item)))
528 (logior ,@(loop for i from 0 below sb!vm:n-word-bytes
529 collect `(ash code ,(* 8 i))))))))
530 `(let ((length (length sequence))
531 (value ,value))
532 (multiple-value-bind (times rem)
533 (truncate length sb!vm:n-word-bytes)
534 (do ((index 0 (1+ index))
535 (end times))
536 ((>= index end)
537 (let ((place (* times sb!vm:n-word-bytes)))
538 (declare (fixnum place))
539 (dotimes (j rem sequence)
540 (declare (index j))
541 (setf (schar sequence (the index (+ place j))) item))))
542 (declare (optimize (speed 3) (safety 0))
543 (type index index))
544 (setf (%vector-raw-bits sequence index) value))))))
546 ;;;; %BYTE-BLT
548 ;;; FIXME: The old CMU CL code used various COPY-TO/FROM-SYSTEM-AREA
549 ;;; stuff (with all the associated bit-index cruft and overflow
550 ;;; issues) even for byte moves. In SBCL, we're converting to byte
551 ;;; moves as problems are discovered with the old code, and this is
552 ;;; currently (ca. sbcl-0.6.12.30) the main interface for code in
553 ;;; SB!KERNEL and SB!SYS (e.g. i/o code). It's not clear that it's the
554 ;;; ideal interface, though, and it probably deserves some thought.
555 (deftransform %byte-blt ((src src-start dst dst-start dst-end)
556 ((or (simple-unboxed-array (*)) system-area-pointer)
557 index
558 (or (simple-unboxed-array (*)) system-area-pointer)
559 index
560 index))
561 ;; FIXME: CMU CL had a hairier implementation of this (back when it
562 ;; was still called (%PRIMITIVE BYTE-BLT). It had the small problem
563 ;; that it didn't work for large (>16M) values of SRC-START or
564 ;; DST-START. However, it might have been more efficient. In
565 ;; particular, I don't really know how much the foreign function
566 ;; call costs us here. My guess is that if the overhead is
567 ;; acceptable for SQRT and COS, it's acceptable here, but this
568 ;; should probably be checked. -- WHN
569 '(flet ((sapify (thing)
570 (etypecase thing
571 (system-area-pointer thing)
572 ;; FIXME: The code here rather relies on the simple
573 ;; unboxed array here having byte-sized entries. That
574 ;; should be asserted explicitly, I just haven't found
575 ;; a concise way of doing it. (It would be nice to
576 ;; declare it in the DEFKNOWN too.)
577 ((simple-unboxed-array (*)) (vector-sap thing)))))
578 (declare (inline sapify))
579 (with-pinned-objects (dst src)
580 (memmove (sap+ (sapify dst) dst-start)
581 (sap+ (sapify src) src-start)
582 (- dst-end dst-start)))
583 (values)))
585 ;;;; transforms for EQL of floating point values
586 #!-float-eql-vops
587 (deftransform eql ((x y) (single-float single-float))
588 '(= (single-float-bits x) (single-float-bits y)))
590 #!-float-eql-vops
591 (deftransform eql ((x y) (double-float double-float))
592 '(and (= (double-float-low-bits x) (double-float-low-bits y))
593 (= (double-float-high-bits x) (double-float-high-bits y))))
596 ;;;; modular functions
598 ;;; FIXME: I think that the :GOODness of a modular function boils down
599 ;;; to whether the normal definition can be used in the middle of a
600 ;;; modular arrangement. LOGAND and LOGIOR can be for all unsigned
601 ;;; modular implementations, I believe, because for all unsigned
602 ;;; arguments of a given size the result of the ordinary definition is
603 ;;; the right one. This should follow through to other logical
604 ;;; functions, such as LOGXOR, should it not? -- CSR, 2007-12-29,
605 ;;; trying to understand a comment he wrote over four years
606 ;;; previously: "FIXME: XOR? ANDC1, ANDC2? -- CSR, 2003-09-16"
607 (define-good-modular-fun logand :untagged nil)
608 (define-good-modular-fun logior :untagged nil)
609 (define-good-modular-fun logxor :untagged nil)
610 (macrolet ((define-good-signed-modular-funs (&rest funs)
611 (let (result)
612 `(progn
613 ,@(dolist (fun funs (nreverse result))
614 (push `(define-good-modular-fun ,fun :untagged t) result)
615 (push `(define-good-modular-fun ,fun :tagged t) result))))))
616 (define-good-signed-modular-funs
617 logand logandc1 logandc2 logeqv logior lognand lognor lognot
618 logorc1 logorc2 logxor))
620 (macrolet
621 ((def (name kind width signedp)
622 (let ((type (ecase signedp
623 ((nil) 'unsigned-byte)
624 ((t) 'signed-byte))))
625 `(progn
626 (defknown ,name (integer (integer 0)) (,type ,width)
627 (foldable flushable movable))
628 (define-modular-fun-optimizer ash ((integer count) ,kind ,signedp :width width)
629 (when (and (<= width ,width)
630 (or (and (constant-lvar-p count)
631 (plusp (lvar-value count)))
632 (csubtypep (lvar-type count)
633 (specifier-type '(and unsigned-byte fixnum)))))
634 (cut-to-width integer ,kind width ,signedp)
635 ',name))
636 (setf (gethash ',name (modular-class-versions (find-modular-class ',kind ',signedp)))
637 `(ash ,',width))))))
638 ;; This should really be dependent on SB!VM:N-WORD-BITS, but since we
639 ;; don't have a true Alpha64 port yet, we'll have to stick to
640 ;; SB!VM:N-MACHINE-WORD-BITS for the time being. --njf, 2004-08-14
641 #.`(progn
642 #!+(or x86 x86-64 arm)
643 (def sb!vm::ash-left-modfx
644 :tagged ,(- sb!vm:n-word-bits sb!vm:n-fixnum-tag-bits) t)
645 (def ,(intern (format nil "ASH-LEFT-MOD~D" sb!vm:n-machine-word-bits)
646 "SB!VM")
647 :untagged ,sb!vm:n-machine-word-bits nil)))
649 ;;;; word-wise logical operations
651 ;;; These transforms assume the presence of modular arithmetic to
652 ;;; generate efficient code.
654 (define-source-transform word-logical-not (x)
655 `(logand (lognot (the sb!vm:word ,x)) #.(1- (ash 1 sb!vm:n-word-bits))))
657 (deftransform word-logical-and ((x y))
658 '(logand x y))
660 (deftransform word-logical-nand ((x y))
661 '(logand (lognand x y) #.(1- (ash 1 sb!vm:n-word-bits))))
663 (deftransform word-logical-or ((x y))
664 '(logior x y))
666 (deftransform word-logical-nor ((x y))
667 '(logand (lognor x y) #.(1- (ash 1 sb!vm:n-word-bits))))
669 (deftransform word-logical-xor ((x y))
670 '(logxor x y))
672 (deftransform word-logical-eqv ((x y))
673 '(logand (logeqv x y) #.(1- (ash 1 sb!vm:n-word-bits))))
675 (deftransform word-logical-orc1 ((x y))
676 '(logand (logorc1 x y) #.(1- (ash 1 sb!vm:n-word-bits))))
678 (deftransform word-logical-orc2 ((x y))
679 '(logand (logorc2 x y) #.(1- (ash 1 sb!vm:n-word-bits))))
681 (deftransform word-logical-andc1 ((x y))
682 '(logand (logandc1 x y) #.(1- (ash 1 sb!vm:n-word-bits))))
684 (deftransform word-logical-andc2 ((x y))
685 '(logand (logandc2 x y) #.(1- (ash 1 sb!vm:n-word-bits))))
688 ;;; There are two different ways the multiplier can be recoded. The
689 ;;; more obvious is to shift X by the correct amount for each bit set
690 ;;; in Y and to sum the results. But if there is a string of bits that
691 ;;; are all set, you can add X shifted by one more then the bit
692 ;;; position of the first set bit and subtract X shifted by the bit
693 ;;; position of the last set bit. We can't use this second method when
694 ;;; the high order bit is bit 31 because shifting by 32 doesn't work
695 ;;; too well.
696 (defun ub32-strength-reduce-constant-multiply (arg num)
697 (declare (type (unsigned-byte 32) num))
698 (let ((adds 0) (shifts 0)
699 (result nil) first-one)
700 (labels ((add (next-factor)
701 (setf result
702 (if result
703 (progn (incf adds) `(+ ,result ,next-factor))
704 next-factor))))
705 (declare (inline add))
706 (dotimes (bitpos 32)
707 (if first-one
708 (when (not (logbitp bitpos num))
709 (add (if (= (1+ first-one) bitpos)
710 ;; There is only a single bit in the string.
711 (progn (incf shifts) `(ash ,arg ,first-one))
712 ;; There are at least two.
713 (progn
714 (incf adds)
715 (incf shifts 2)
716 `(- (ash ,arg ,bitpos)
717 (ash ,arg ,first-one)))))
718 (setf first-one nil))
719 (when (logbitp bitpos num)
720 (setf first-one bitpos))))
721 (when first-one
722 (cond ((= first-one 31))
723 ((= first-one 30) (incf shifts) (add `(ash ,arg 30)))
725 (incf shifts 2)
726 (incf adds)
727 (add `(- (ash ,arg 31)
728 (ash ,arg ,first-one)))))
729 (incf shifts)
730 (add `(ash ,arg 31))))
731 (values (if (plusp adds)
732 `(logand ,result #.(1- (ash 1 32))) ; using modular arithmetic
733 result)
734 adds
735 shifts)))
738 ;;; Transform GET-LISP-OBJ-ADDRESS for constant immediates, since the normal
739 ;;; VOP can't handle them.
741 (deftransform sb!vm::get-lisp-obj-address ((obj) ((constant-arg fixnum)))
742 (ash (lvar-value obj) sb!vm::n-fixnum-tag-bits))
744 (deftransform sb!vm::get-lisp-obj-address ((obj) ((constant-arg character)))
745 (logior sb!vm::character-widetag
746 (ash (char-code (lvar-value obj)) sb!vm::n-widetag-bits)))