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