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