0.9.2.48:
[sbcl.git] / src / compiler / x86 / type-vops.lisp
1 ;;;; type testing and checking VOPs for the x86 VM
2
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.
11
12 (in-package "SB!VM")
13 \f
14 ;;;; test generation utilities
15
16 ;;; Emit the most compact form of the test immediate instruction,
17 ;;; using an 8 bit test when the immediate is only 8 bits and the
18 ;;; value is one of the four low registers (eax, ebx, ecx, edx) or the
19 ;;; control stack.
20 (defun generate-fixnum-test (value)
21   (let ((offset (tn-offset value)))
22     (cond ((and (sc-is value any-reg descriptor-reg)
23                 (or (= offset eax-offset) (= offset ebx-offset)
24                     (= offset ecx-offset) (= offset edx-offset)))
25            (inst test (make-random-tn :kind :normal
26                                       :sc (sc-or-lose 'byte-reg)
27                                       :offset offset)
28                  3))
29           ((sc-is value control-stack)
30            (inst test (make-ea :byte :base ebp-tn
31                                :disp (- (* (1+ offset) n-word-bytes)))
32                  3))
33           (t
34            (inst test value 3)))))
35
36 (defun %test-fixnum (value target not-p)
37   (generate-fixnum-test value)
38   (inst jmp (if not-p :nz :z) target))
39
40 (defun %test-fixnum-and-headers (value target not-p headers)
41   (let ((drop-through (gen-label)))
42     (generate-fixnum-test value)
43     (inst jmp :z (if not-p drop-through target))
44     (%test-headers value target not-p nil headers drop-through)))
45
46 (defun %test-immediate (value target not-p immediate)
47   ;; Code a single instruction byte test if possible.
48   (let ((offset (tn-offset value)))
49     (cond ((and (sc-is value any-reg descriptor-reg)
50                 (or (= offset eax-offset) (= offset ebx-offset)
51                     (= offset ecx-offset) (= offset edx-offset)))
52            (inst cmp (make-random-tn :kind :normal
53                                      :sc (sc-or-lose 'byte-reg)
54                                      :offset offset)
55                  immediate))
56           (t
57            (move eax-tn value)
58            (inst cmp al-tn immediate))))
59   (inst jmp (if not-p :ne :e) target))
60
61 (defun %test-lowtag (value target not-p lowtag &optional al-loaded)
62   (unless al-loaded
63     (move eax-tn value)
64     (inst and al-tn lowtag-mask))
65   ;; FIXME: another 'optimization' which doesn't appear to work:
66   ;; prefetching the hypothetically pointed-to version should help,
67   ;; but this is in fact non-ideal in plenty of ways: we emit way too
68   ;; many of these prefetch instructions; pointed-to objects are very
69   ;; often in the cache anyway; etc. etc.  Still, as proof-of-concept,
70   ;; not too bad.  -- CSR, 2004-07-27
71   (when (member :prefetch *backend-subfeatures*)
72     (inst prefetchnta (make-ea :byte :base value :disp (- lowtag))))
73   (inst cmp al-tn lowtag)
74   (inst jmp (if not-p :ne :e) target))
75
76 (defun %test-headers (value target not-p function-p headers
77                             &optional (drop-through (gen-label)) al-loaded)
78   (let ((lowtag (if function-p fun-pointer-lowtag other-pointer-lowtag)))
79     (multiple-value-bind (equal less-or-equal greater-or-equal when-true when-false)
80         ;; EQUAL, LESS-OR-EQUAL and GREATER-OR-EQUAL are the conditions for
81         ;; branching to TARGET.  WHEN-TRUE and WHEN-FALSE are the
82         ;; labels to branch to when we know it's true and when we know
83         ;; it's false respectively.
84         (if not-p
85             (values :ne :a :b drop-through target)
86             (values :e :na :nb target drop-through))
87       (%test-lowtag value when-false t lowtag al-loaded)
88       (inst mov al-tn (make-ea :byte :base value :disp (- lowtag)))
89       (do ((remaining headers (cdr remaining)))
90           ((null remaining))
91         (let ((header (car remaining))
92               (last (null (cdr remaining))))
93           (cond
94            ((atom header)
95             (cond
96               ((and (not last) (null (cddr remaining))
97                     (atom (cadr remaining))
98                     (= (logcount (logxor header (cadr remaining))) 1))
99                ;; BASE-STRING, (VECTOR NIL), BIT-VECTOR, (VECTOR T)
100                (inst and al-tn (ldb (byte 8 0) (logeqv header (cadr remaining))))
101                (inst cmp al-tn (ldb (byte 8 0) (logand header (cadr remaining))))
102                (inst jmp equal target)
103                (return))
104               (t
105                (inst cmp al-tn header)
106                (if last
107                    (inst jmp equal target)
108                    (inst jmp :e when-true)))))
109            (t
110              (let ((start (car header))
111                    (end (cdr header)))
112                (cond
113                  ;; LAST = don't need al-tn later
114                  ((and last (not (= start bignum-widetag))
115                        (= (+ start 4) end) (= (logcount (logxor start end)) 1))
116                   ;; SIMPLE-STRING
117                   (inst and al-tn (ldb (byte 8 0) (logeqv start end)))
118                   (inst cmp al-tn (ldb (byte 8 0) (logand start end)))
119                   (inst jmp equal target))
120                  ((and (not last) (null (cddr remaining))
121                        (= (+ start 4) end) (= (logcount (logxor start end)) 1)
122                        (listp (cadr remaining))
123                        (= (+ (caadr remaining) 4) (cdadr remaining))
124                        (= (logcount (logxor (caadr remaining) (cdadr remaining))) 1)
125                        (= (logcount (logxor (caadr remaining) start)) 1))
126                   ;; STRING
127                   (inst and al-tn (ldb (byte 8 0) (logeqv start (cdadr remaining))))
128                   (inst cmp al-tn (ldb (byte 8 0) (logand start (cdadr remaining))))
129                   (inst jmp equal target)
130                   ;; we've shortcircuited the DO, so we must return.
131                   ;; It's OK to do so, because (NULL (CDDR REMAINING))
132                   ;; was true.
133                   (return))
134                  (t
135                   (unless (= start bignum-widetag)
136                     (inst cmp al-tn start)
137                     (if (= end complex-array-widetag)
138                         (progn
139                           (aver last)
140                           (inst jmp greater-or-equal target))
141                         (inst jmp :b when-false))) ; was :l
142                   (unless (= end complex-array-widetag)
143                     (inst cmp al-tn end)
144                     (if last
145                         (inst jmp less-or-equal target)
146                         (inst jmp :be when-true)))))))))) ; was :le
147       (emit-label drop-through))))
148 \f
149 ;;;; type checking and testing
150
151 (define-vop (check-type)
152   (:args (value :target result :scs (any-reg descriptor-reg)))
153   (:results (result :scs (any-reg descriptor-reg)))
154   (:temporary (:sc unsigned-reg :offset eax-offset :to (:result 0)) eax)
155   (:ignore eax)
156   (:vop-var vop)
157   (:save-p :compute-only))
158
159 (define-vop (type-predicate)
160   (:args (value :scs (any-reg descriptor-reg)))
161   (:temporary (:sc unsigned-reg :offset eax-offset) eax)
162   (:ignore eax)
163   (:conditional)
164   (:info target not-p)
165   (:policy :fast-safe))
166
167 ;;; simpler VOP that don't need a temporary register
168 (define-vop (simple-check-type)
169   (:args (value :target result :scs (any-reg descriptor-reg)))
170   (:results (result :scs (any-reg descriptor-reg)
171                     :load-if (not (and (sc-is value any-reg descriptor-reg)
172                                        (sc-is result control-stack)))))
173   (:vop-var vop)
174   (:save-p :compute-only))
175
176 (define-vop (simple-type-predicate)
177   (:args (value :scs (any-reg descriptor-reg control-stack)))
178   (:conditional)
179   (:info target not-p)
180   (:policy :fast-safe))
181
182 (defun cost-to-test-types (type-codes)
183   (+ (* 2 (length type-codes))
184      (if (> (apply #'max type-codes) lowtag-limit) 7 2)))
185
186 (defmacro !define-type-vops (pred-name check-name ptype error-code
187                              (&rest type-codes)
188                              &key (variant nil variant-p) &allow-other-keys)
189   ;; KLUDGE: UGH. Why do we need this eval? Can't we put this in the
190   ;; expansion?
191   (let* ((cost (cost-to-test-types (mapcar #'eval type-codes)))
192          (prefix (if variant-p
193                      (concatenate 'string (string variant) "-")
194                      "")))
195     `(progn
196        ,@(when pred-name
197            `((define-vop (,pred-name ,(intern (concatenate 'string prefix "TYPE-PREDICATE")))
198                (:translate ,pred-name)
199                (:generator ,cost
200                  (test-type value target not-p (,@type-codes))))))
201        ,@(when check-name
202            `((define-vop (,check-name ,(intern (concatenate 'string prefix "CHECK-TYPE")))
203                (:generator ,cost
204                  (let ((err-lab
205                         (generate-error-code vop ,error-code value)))
206                    (test-type value err-lab t (,@type-codes))
207                    (move result value))))))
208        ,@(when ptype
209            `((primitive-type-vop ,check-name (:check) ,ptype))))))
210 \f
211 ;;;; other integer ranges
212
213 (define-vop (fixnump/unsigned-byte-32 simple-type-predicate)
214   (:args (value :scs (unsigned-reg)))
215   (:arg-types unsigned-num)
216   (:translate fixnump)
217   (:generator 5
218     (inst cmp value #.sb!xc:most-positive-fixnum)
219     (inst jmp (if not-p :a :be) target)))
220
221 ;;; A (SIGNED-BYTE 32) can be represented with either fixnum or a bignum with
222 ;;; exactly one digit.
223
224 (define-vop (signed-byte-32-p type-predicate)
225   (:translate signed-byte-32-p)
226   (:generator 45
227     (multiple-value-bind (yep nope)
228         (if not-p
229             (values not-target target)
230             (values target not-target))
231       (generate-fixnum-test value)
232       (inst jmp :e yep)
233       (move eax-tn value)
234       (inst and al-tn lowtag-mask)
235       (inst cmp al-tn other-pointer-lowtag)
236       (inst jmp :ne nope)
237       (loadw eax-tn value 0 other-pointer-lowtag)
238       (inst cmp eax-tn (+ (ash 1 n-widetag-bits) bignum-widetag))
239       (inst jmp (if not-p :ne :e) target))
240     NOT-TARGET))
241
242 (define-vop (check-signed-byte-32 check-type)
243   (:generator 45
244     (let ((nope (generate-error-code vop
245                                      object-not-signed-byte-32-error
246                                      value)))
247       (generate-fixnum-test value)
248       (inst jmp :e yep)
249       (move eax-tn value)
250       (inst and al-tn lowtag-mask)
251       (inst cmp al-tn other-pointer-lowtag)
252       (inst jmp :ne nope)
253       (loadw eax-tn value 0 other-pointer-lowtag)
254       (inst cmp eax-tn (+ (ash 1 n-widetag-bits) bignum-widetag))
255       (inst jmp :ne nope))
256     YEP
257     (move result value)))
258
259 ;;; An (unsigned-byte 32) can be represented with either a positive
260 ;;; fixnum, a bignum with exactly one positive digit, or a bignum with
261 ;;; exactly two digits and the second digit all zeros.
262 (define-vop (unsigned-byte-32-p type-predicate)
263   (:translate unsigned-byte-32-p)
264   (:generator 45
265     (let ((not-target (gen-label))
266           (single-word (gen-label))
267           (fixnum (gen-label)))
268       (multiple-value-bind (yep nope)
269           (if not-p
270               (values not-target target)
271               (values target not-target))
272         ;; Is it a fixnum?
273         (generate-fixnum-test value)
274         (move eax-tn value)
275         (inst jmp :e fixnum)
276
277         ;; If not, is it an other pointer?
278         (inst and al-tn lowtag-mask)
279         (inst cmp al-tn other-pointer-lowtag)
280         (inst jmp :ne nope)
281         ;; Get the header.
282         (loadw eax-tn value 0 other-pointer-lowtag)
283         ;; Is it one?
284         (inst cmp eax-tn (+ (ash 1 n-widetag-bits) bignum-widetag))
285         (inst jmp :e single-word)
286         ;; If it's other than two, we can't be an (unsigned-byte 32)
287         (inst cmp eax-tn (+ (ash 2 n-widetag-bits) bignum-widetag))
288         (inst jmp :ne nope)
289         ;; Get the second digit.
290         (loadw eax-tn value (1+ bignum-digits-offset) other-pointer-lowtag)
291         ;; All zeros, its an (unsigned-byte 32).
292         (inst or eax-tn eax-tn)
293         (inst jmp :z yep)
294         (inst jmp nope)
295
296         (emit-label single-word)
297         ;; Get the single digit.
298         (loadw eax-tn value bignum-digits-offset other-pointer-lowtag)
299
300         ;; positive implies (unsigned-byte 32).
301         (emit-label fixnum)
302         (inst or eax-tn eax-tn)
303         (inst jmp (if not-p :s :ns) target)
304
305         (emit-label not-target)))))
306
307 (define-vop (check-unsigned-byte-32 check-type)
308   (:generator 45
309     (let ((nope
310            (generate-error-code vop object-not-unsigned-byte-32-error value))
311           (yep (gen-label))
312           (fixnum (gen-label))
313           (single-word (gen-label)))
314
315       ;; Is it a fixnum?
316       (generate-fixnum-test value)
317       (move eax-tn value)
318       (inst jmp :e fixnum)
319
320       ;; If not, is it an other pointer?
321       (inst and al-tn lowtag-mask)
322       (inst cmp al-tn other-pointer-lowtag)
323       (inst jmp :ne nope)
324       ;; Get the header.
325       (loadw eax-tn value 0 other-pointer-lowtag)
326       ;; Is it one?
327       (inst cmp eax-tn (+ (ash 1 n-widetag-bits) bignum-widetag))
328       (inst jmp :e single-word)
329       ;; If it's other than two, we can't be an (unsigned-byte 32)
330       (inst cmp eax-tn (+ (ash 2 n-widetag-bits) bignum-widetag))
331       (inst jmp :ne nope)
332       ;; Get the second digit.
333       (loadw eax-tn value (1+ bignum-digits-offset) other-pointer-lowtag)
334       ;; All zeros, its an (unsigned-byte 32).
335       (inst or eax-tn eax-tn)
336       (inst jmp :z yep)
337       (inst jmp nope)
338
339       (emit-label single-word)
340       ;; Get the single digit.
341       (loadw eax-tn value bignum-digits-offset other-pointer-lowtag)
342
343       ;; positive implies (unsigned-byte 32).
344       (emit-label fixnum)
345       (inst or eax-tn eax-tn)
346       (inst jmp :s nope)
347
348       (emit-label yep)
349       (move result value))))
350 \f
351 ;;;; list/symbol types
352 ;;;
353 ;;; symbolp (or symbol (eq nil))
354 ;;; consp (and list (not (eq nil)))
355
356 (define-vop (symbolp type-predicate)
357   (:translate symbolp)
358   (:generator 12
359     (let ((is-symbol-label (if not-p drop-thru target)))
360       (inst cmp value nil-value)
361       (inst jmp :e is-symbol-label)
362       (test-type value target not-p (symbol-header-widetag)))
363     DROP-THRU))
364
365 (define-vop (check-symbol check-type)
366   (:generator 12
367     (let ((error (generate-error-code vop object-not-symbol-error value)))
368       (inst cmp value nil-value)
369       (inst jmp :e drop-thru)
370       (test-type value error t (symbol-header-widetag)))
371     DROP-THRU
372     (move result value)))
373
374 (define-vop (consp type-predicate)
375   (:translate consp)
376   (:generator 8
377     (let ((is-not-cons-label (if not-p target drop-thru)))
378       (inst cmp value nil-value)
379       (inst jmp :e is-not-cons-label)
380       (test-type value target not-p (list-pointer-lowtag)))
381     DROP-THRU))
382
383 (define-vop (check-cons check-type)
384   (:generator 8
385     (let ((error (generate-error-code vop object-not-cons-error value)))
386       (inst cmp value nil-value)
387       (inst jmp :e error)
388       (test-type value error t (list-pointer-lowtag))
389       (move result value))))