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