0.7.7.20-backend-cleanup-1.1:
[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 def-type-vops (pred-name check-name ptype error-code
151                                    &rest type-codes)
152   (let ((cost (cost-to-test-types (mapcar #'eval type-codes))))
153     `(progn
154        ,@(when pred-name
155            `((define-vop (,pred-name type-predicate)
156                (:translate ,pred-name)
157                (:generator ,cost
158                  (test-type value target not-p ,@type-codes)))))
159        ,@(when check-name
160            `((define-vop (,check-name check-type)
161                (:generator ,cost
162                  (let ((err-lab
163                         (generate-error-code vop ,error-code value)))
164                    (test-type value err-lab t ,@type-codes)
165                    (move result value))))))
166        ,@(when ptype
167            `((primitive-type-vop ,check-name (:check) ,ptype))))))
168
169 (defmacro def-simple-type-vops (pred-name check-name ptype error-code
170                                           &rest type-codes)
171   (let ((cost (cost-to-test-types (mapcar #'eval type-codes))))
172     `(progn
173        ,@(when pred-name
174            `((define-vop (,pred-name simple-type-predicate)
175                (:translate ,pred-name)
176                (:generator ,cost
177                  (test-type value target not-p ,@type-codes)))))
178        ,@(when check-name
179            `((define-vop (,check-name simple-check-type)
180                (:generator ,cost
181                  (let ((err-lab
182                         (generate-error-code vop ,error-code value)))
183                    (test-type value err-lab t ,@type-codes)
184                    (move result value))))))
185        ,@(when ptype
186            `((primitive-type-vop ,check-name (:check) ,ptype))))))
187 \f
188 ;;;; other integer ranges
189
190 ;;; A (SIGNED-BYTE 32) can be represented with either fixnum or a bignum with
191 ;;; exactly one digit.
192
193 (define-vop (signed-byte-32-p type-predicate)
194   (:translate signed-byte-32-p)
195   (:generator 45
196     (multiple-value-bind (yep nope)
197         (if not-p
198             (values not-target target)
199             (values target not-target))
200       (generate-fixnum-test value)
201       (inst jmp :e yep)
202       (move eax-tn value)
203       (inst and al-tn lowtag-mask)
204       (inst cmp al-tn other-pointer-lowtag)
205       (inst jmp :ne nope)
206       (loadw eax-tn value 0 other-pointer-lowtag)
207       (inst cmp eax-tn (+ (ash 1 n-widetag-bits) bignum-widetag))
208       (inst jmp (if not-p :ne :e) target))
209     NOT-TARGET))
210
211 (define-vop (check-signed-byte-32 check-type)
212   (:generator 45
213     (let ((nope (generate-error-code vop
214                                      object-not-signed-byte-32-error
215                                      value)))
216       (generate-fixnum-test value)
217       (inst jmp :e yep)
218       (move eax-tn value)
219       (inst and al-tn lowtag-mask)
220       (inst cmp al-tn other-pointer-lowtag)
221       (inst jmp :ne nope)
222       (loadw eax-tn value 0 other-pointer-lowtag)
223       (inst cmp eax-tn (+ (ash 1 n-widetag-bits) bignum-widetag))
224       (inst jmp :ne nope))
225     YEP
226     (move result value)))
227
228 ;;; An (unsigned-byte 32) can be represented with either a positive
229 ;;; fixnum, a bignum with exactly one positive digit, or a bignum with
230 ;;; exactly two digits and the second digit all zeros.
231 (define-vop (unsigned-byte-32-p type-predicate)
232   (:translate unsigned-byte-32-p)
233   (:generator 45
234     (let ((not-target (gen-label))
235           (single-word (gen-label))
236           (fixnum (gen-label)))
237       (multiple-value-bind (yep nope)
238           (if not-p
239               (values not-target target)
240               (values target not-target))
241         ;; Is it a fixnum?
242         (generate-fixnum-test value)
243         (move eax-tn value)
244         (inst jmp :e fixnum)
245
246         ;; If not, is it an other pointer?
247         (inst and al-tn lowtag-mask)
248         (inst cmp al-tn other-pointer-lowtag)
249         (inst jmp :ne nope)
250         ;; Get the header.
251         (loadw eax-tn value 0 other-pointer-lowtag)
252         ;; Is it one?
253         (inst cmp eax-tn (+ (ash 1 n-widetag-bits) bignum-widetag))
254         (inst jmp :e single-word)
255         ;; If it's other than two, we can't be an (unsigned-byte 32)
256         (inst cmp eax-tn (+ (ash 2 n-widetag-bits) bignum-widetag))
257         (inst jmp :ne nope)
258         ;; Get the second digit.
259         (loadw eax-tn value (1+ bignum-digits-offset) other-pointer-lowtag)
260         ;; All zeros, its an (unsigned-byte 32).
261         (inst or eax-tn eax-tn)
262         (inst jmp :z yep)
263         (inst jmp nope)
264         
265         (emit-label single-word)
266         ;; Get the single digit.
267         (loadw eax-tn value bignum-digits-offset other-pointer-lowtag)
268
269         ;; positive implies (unsigned-byte 32).
270         (emit-label fixnum)
271         (inst or eax-tn eax-tn)
272         (inst jmp (if not-p :s :ns) target)
273
274         (emit-label not-target)))))
275
276 (define-vop (check-unsigned-byte-32 check-type)
277   (:generator 45
278     (let ((nope
279            (generate-error-code vop object-not-unsigned-byte-32-error value))
280           (yep (gen-label))
281           (fixnum (gen-label))
282           (single-word (gen-label)))
283
284       ;; Is it a fixnum?
285       (generate-fixnum-test value)
286       (move eax-tn value)
287       (inst jmp :e fixnum)
288
289       ;; If not, is it an other pointer?
290       (inst and al-tn lowtag-mask)
291       (inst cmp al-tn other-pointer-lowtag)
292       (inst jmp :ne nope)
293       ;; Get the header.
294       (loadw eax-tn value 0 other-pointer-lowtag)
295       ;; Is it one?
296       (inst cmp eax-tn (+ (ash 1 n-widetag-bits) bignum-widetag))
297       (inst jmp :e single-word)
298       ;; If it's other than two, we can't be an (unsigned-byte 32)
299       (inst cmp eax-tn (+ (ash 2 n-widetag-bits) bignum-widetag))
300       (inst jmp :ne nope)
301       ;; Get the second digit.
302       (loadw eax-tn value (1+ bignum-digits-offset) other-pointer-lowtag)
303       ;; All zeros, its an (unsigned-byte 32).
304       (inst or eax-tn eax-tn)
305       (inst jmp :z yep)
306       (inst jmp nope)
307         
308       (emit-label single-word)
309       ;; Get the single digit.
310       (loadw eax-tn value bignum-digits-offset other-pointer-lowtag)
311
312       ;; positive implies (unsigned-byte 32).
313       (emit-label fixnum)
314       (inst or eax-tn eax-tn)
315       (inst jmp :s nope)
316
317       (emit-label yep)
318       (move result value))))
319 \f
320 ;;;; list/symbol types
321 ;;;
322 ;;; symbolp (or symbol (eq nil))
323 ;;; consp (and list (not (eq nil)))
324
325 (define-vop (symbolp type-predicate)
326   (:translate symbolp)
327   (:generator 12
328     (let ((is-symbol-label (if not-p drop-thru target)))
329       (inst cmp value nil-value)
330       (inst jmp :e is-symbol-label)
331       (test-type value target not-p symbol-header-widetag))
332     DROP-THRU))
333
334 (define-vop (check-symbol check-type)
335   (:generator 12
336     (let ((error (generate-error-code vop object-not-symbol-error value)))
337       (inst cmp value nil-value)
338       (inst jmp :e drop-thru)
339       (test-type value error t symbol-header-widetag))
340     DROP-THRU
341     (move result value)))
342
343 (define-vop (consp type-predicate)
344   (:translate consp)
345   (:generator 8
346     (let ((is-not-cons-label (if not-p target drop-thru)))
347       (inst cmp value nil-value)
348       (inst jmp :e is-not-cons-label)
349       (test-type value target not-p list-pointer-lowtag))
350     DROP-THRU))
351
352 (define-vop (check-cons check-type)
353   (:generator 8
354     (let ((error (generate-error-code vop object-not-cons-error value)))
355       (inst cmp value nil-value)
356       (inst jmp :e error)
357       (test-type value error t list-pointer-lowtag)
358       (move result value))))