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