0.8.1.31:
[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   (inst cmp al-tn lowtag)
66   (inst jmp (if not-p :ne :e) target))
67
68 (defun %test-headers (value target not-p function-p headers
69                             &optional (drop-through (gen-label)) al-loaded)
70   (let ((lowtag (if function-p fun-pointer-lowtag other-pointer-lowtag)))
71     (multiple-value-bind (equal less-or-equal when-true when-false)
72         ;; EQUAL and LESS-OR-EQUAL are the conditions for branching to TARGET.
73         ;; WHEN-TRUE and WHEN-FALSE are the labels to branch to when we know
74         ;; it's true and when we know it's false respectively.
75         (if not-p
76             (values :ne :a drop-through target)
77             (values :e :na target drop-through))
78       (%test-lowtag value when-false t lowtag al-loaded)
79       (inst mov al-tn (make-ea :byte :base value :disp (- lowtag)))
80       (do ((remaining headers (cdr remaining)))
81           ((null remaining))
82         (let ((header (car remaining))
83               (last (null (cdr remaining))))
84           (cond
85            ((atom header)
86             (inst cmp al-tn header)
87             (if last
88                 (inst jmp equal target)
89                 (inst jmp :e when-true)))
90            (t
91              (let ((start (car header))
92                    (end (cdr header)))
93                (unless (= start bignum-widetag)
94                  (inst cmp al-tn start)
95                  (inst jmp :b when-false)) ; was :l
96                (inst cmp al-tn end)
97                (if last
98                    (inst jmp less-or-equal target)
99                    (inst jmp :be when-true))))))) ; was :le
100       (emit-label drop-through))))
101
102 \f
103 ;;;; type checking and testing
104
105 (define-vop (check-type)
106   (:args (value :target result :scs (any-reg descriptor-reg)))
107   (:results (result :scs (any-reg descriptor-reg)))
108   (:temporary (:sc unsigned-reg :offset eax-offset :to (:result 0)) eax)
109   (:ignore eax)
110   (:vop-var vop)
111   (:save-p :compute-only))
112
113 (define-vop (type-predicate)
114   (:args (value :scs (any-reg descriptor-reg)))
115   (:temporary (:sc unsigned-reg :offset eax-offset) eax)
116   (:ignore eax)
117   (:conditional)
118   (:info target not-p)
119   (:policy :fast-safe))
120
121 ;;; simpler VOP that don't need a temporary register
122 (define-vop (simple-check-type)
123   (:args (value :target result :scs (any-reg descriptor-reg)))
124   (:results (result :scs (any-reg descriptor-reg)
125                     :load-if (not (and (sc-is value any-reg descriptor-reg)
126                                        (sc-is result control-stack)))))
127   (:vop-var vop)
128   (:save-p :compute-only))
129
130 (define-vop (simple-type-predicate)
131   (:args (value :scs (any-reg descriptor-reg control-stack)))
132   (:conditional)
133   (:info target not-p)
134   (:policy :fast-safe))
135
136 (defun cost-to-test-types (type-codes)
137   (+ (* 2 (length type-codes))
138      (if (> (apply #'max type-codes) lowtag-limit) 7 2)))
139
140 (defmacro !define-type-vops (pred-name check-name ptype error-code
141                              (&rest type-codes)
142                              &key (variant nil variant-p) &allow-other-keys)
143   ;; KLUDGE: UGH. Why do we need this eval? Can't we put this in the
144   ;; expansion?
145   (let* ((cost (cost-to-test-types (mapcar #'eval type-codes)))
146          (prefix (if variant-p
147                      (concatenate 'string (string variant) "-")
148                      "")))
149     `(progn
150        ,@(when pred-name
151            `((define-vop (,pred-name ,(intern (concatenate 'string prefix "TYPE-PREDICATE")))
152                (:translate ,pred-name)
153                (:generator ,cost
154                  (test-type value target not-p (,@type-codes))))))
155        ,@(when check-name
156            `((define-vop (,check-name ,(intern (concatenate 'string prefix "CHECK-TYPE")))
157                (:generator ,cost
158                  (let ((err-lab
159                         (generate-error-code vop ,error-code value)))
160                    (test-type value err-lab t (,@type-codes))
161                    (move result value))))))
162        ,@(when ptype
163            `((primitive-type-vop ,check-name (:check) ,ptype))))))
164 \f
165 ;;;; other integer ranges
166
167 (define-vop (fixnump/unsigned-byte-32 simple-type-predicate)
168   (:args (value :scs (unsigned-reg)))
169   (:arg-types unsigned-num)
170   (:translate fixnump)
171   (:generator 5
172     (inst cmp value #.sb!xc:most-positive-fixnum)
173     (inst jmp (if not-p :a :be) target)))
174
175 ;;; A (SIGNED-BYTE 32) can be represented with either fixnum or a bignum with
176 ;;; exactly one digit.
177
178 (define-vop (signed-byte-32-p type-predicate)
179   (:translate signed-byte-32-p)
180   (:generator 45
181     (multiple-value-bind (yep nope)
182         (if not-p
183             (values not-target target)
184             (values target not-target))
185       (generate-fixnum-test value)
186       (inst jmp :e yep)
187       (move eax-tn value)
188       (inst and al-tn lowtag-mask)
189       (inst cmp al-tn other-pointer-lowtag)
190       (inst jmp :ne nope)
191       (loadw eax-tn value 0 other-pointer-lowtag)
192       (inst cmp eax-tn (+ (ash 1 n-widetag-bits) bignum-widetag))
193       (inst jmp (if not-p :ne :e) target))
194     NOT-TARGET))
195
196 (define-vop (check-signed-byte-32 check-type)
197   (:generator 45
198     (let ((nope (generate-error-code vop
199                                      object-not-signed-byte-32-error
200                                      value)))
201       (generate-fixnum-test value)
202       (inst jmp :e yep)
203       (move eax-tn value)
204       (inst and al-tn lowtag-mask)
205       (inst cmp al-tn other-pointer-lowtag)
206       (inst jmp :ne nope)
207       (loadw eax-tn value 0 other-pointer-lowtag)
208       (inst cmp eax-tn (+ (ash 1 n-widetag-bits) bignum-widetag))
209       (inst jmp :ne nope))
210     YEP
211     (move result value)))
212
213 ;;; An (unsigned-byte 32) can be represented with either a positive
214 ;;; fixnum, a bignum with exactly one positive digit, or a bignum with
215 ;;; exactly two digits and the second digit all zeros.
216 (define-vop (unsigned-byte-32-p type-predicate)
217   (:translate unsigned-byte-32-p)
218   (:generator 45
219     (let ((not-target (gen-label))
220           (single-word (gen-label))
221           (fixnum (gen-label)))
222       (multiple-value-bind (yep nope)
223           (if not-p
224               (values not-target target)
225               (values target not-target))
226         ;; Is it a fixnum?
227         (generate-fixnum-test value)
228         (move eax-tn value)
229         (inst jmp :e fixnum)
230
231         ;; If not, is it an other pointer?
232         (inst and al-tn lowtag-mask)
233         (inst cmp al-tn other-pointer-lowtag)
234         (inst jmp :ne nope)
235         ;; Get the header.
236         (loadw eax-tn value 0 other-pointer-lowtag)
237         ;; Is it one?
238         (inst cmp eax-tn (+ (ash 1 n-widetag-bits) bignum-widetag))
239         (inst jmp :e single-word)
240         ;; If it's other than two, we can't be an (unsigned-byte 32)
241         (inst cmp eax-tn (+ (ash 2 n-widetag-bits) bignum-widetag))
242         (inst jmp :ne nope)
243         ;; Get the second digit.
244         (loadw eax-tn value (1+ bignum-digits-offset) other-pointer-lowtag)
245         ;; All zeros, its an (unsigned-byte 32).
246         (inst or eax-tn eax-tn)
247         (inst jmp :z yep)
248         (inst jmp nope)
249         
250         (emit-label single-word)
251         ;; Get the single digit.
252         (loadw eax-tn value bignum-digits-offset other-pointer-lowtag)
253
254         ;; positive implies (unsigned-byte 32).
255         (emit-label fixnum)
256         (inst or eax-tn eax-tn)
257         (inst jmp (if not-p :s :ns) target)
258
259         (emit-label not-target)))))
260
261 (define-vop (check-unsigned-byte-32 check-type)
262   (:generator 45
263     (let ((nope
264            (generate-error-code vop object-not-unsigned-byte-32-error value))
265           (yep (gen-label))
266           (fixnum (gen-label))
267           (single-word (gen-label)))
268
269       ;; Is it a fixnum?
270       (generate-fixnum-test value)
271       (move eax-tn value)
272       (inst jmp :e fixnum)
273
274       ;; If not, is it an other pointer?
275       (inst and al-tn lowtag-mask)
276       (inst cmp al-tn other-pointer-lowtag)
277       (inst jmp :ne nope)
278       ;; Get the header.
279       (loadw eax-tn value 0 other-pointer-lowtag)
280       ;; Is it one?
281       (inst cmp eax-tn (+ (ash 1 n-widetag-bits) bignum-widetag))
282       (inst jmp :e single-word)
283       ;; If it's other than two, we can't be an (unsigned-byte 32)
284       (inst cmp eax-tn (+ (ash 2 n-widetag-bits) bignum-widetag))
285       (inst jmp :ne nope)
286       ;; Get the second digit.
287       (loadw eax-tn value (1+ bignum-digits-offset) other-pointer-lowtag)
288       ;; All zeros, its an (unsigned-byte 32).
289       (inst or eax-tn eax-tn)
290       (inst jmp :z yep)
291       (inst jmp nope)
292         
293       (emit-label single-word)
294       ;; Get the single digit.
295       (loadw eax-tn value bignum-digits-offset other-pointer-lowtag)
296
297       ;; positive implies (unsigned-byte 32).
298       (emit-label fixnum)
299       (inst or eax-tn eax-tn)
300       (inst jmp :s nope)
301
302       (emit-label yep)
303       (move result value))))
304 \f
305 ;;;; list/symbol types
306 ;;;
307 ;;; symbolp (or symbol (eq nil))
308 ;;; consp (and list (not (eq nil)))
309
310 (define-vop (symbolp type-predicate)
311   (:translate symbolp)
312   (:generator 12
313     (let ((is-symbol-label (if not-p drop-thru target)))
314       (inst cmp value nil-value)
315       (inst jmp :e is-symbol-label)
316       (test-type value target not-p (symbol-header-widetag)))
317     DROP-THRU))
318
319 (define-vop (check-symbol check-type)
320   (:generator 12
321     (let ((error (generate-error-code vop object-not-symbol-error value)))
322       (inst cmp value nil-value)
323       (inst jmp :e drop-thru)
324       (test-type value error t (symbol-header-widetag)))
325     DROP-THRU
326     (move result value)))
327
328 (define-vop (consp type-predicate)
329   (:translate consp)
330   (:generator 8
331     (let ((is-not-cons-label (if not-p target drop-thru)))
332       (inst cmp value nil-value)
333       (inst jmp :e is-not-cons-label)
334       (test-type value target not-p (list-pointer-lowtag)))
335     DROP-THRU))
336
337 (define-vop (check-cons check-type)
338   (:generator 8
339     (let ((error (generate-error-code vop object-not-cons-error value)))
340       (inst cmp value nil-value)
341       (inst jmp :e error)
342       (test-type value error t (list-pointer-lowtag))
343       (move result value))))