1.0.16.10: function-ify ERROR-CALL and GENERATE-ERROR-CODE on x86
[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 (defun generate-fixnum-test (value)
17   (emit-optimized-test-inst value 3))
18
19 (defun %test-fixnum (value target not-p)
20   (generate-fixnum-test value)
21   (inst jmp (if not-p :nz :z) target))
22
23 (defun %test-fixnum-and-headers (value target not-p headers)
24   (let ((drop-through (gen-label)))
25     (generate-fixnum-test value)
26     (inst jmp :z (if not-p drop-through target))
27     (%test-headers value target not-p nil headers drop-through)))
28
29 (defun %test-immediate (value target not-p immediate)
30   ;; Code a single instruction byte test if possible.
31   (let ((offset (tn-offset value)))
32     (cond ((and (sc-is value any-reg descriptor-reg)
33                 (or (= offset eax-offset) (= offset ebx-offset)
34                     (= offset ecx-offset) (= offset edx-offset)))
35            (inst cmp (make-random-tn :kind :normal
36                                      :sc (sc-or-lose 'byte-reg)
37                                      :offset offset)
38                  immediate))
39           (t
40            (move eax-tn value)
41            (inst cmp al-tn immediate))))
42   (inst jmp (if not-p :ne :e) target))
43
44 (defun %test-lowtag (value target not-p lowtag &optional al-loaded)
45   (unless al-loaded
46     (move eax-tn value)
47     (inst and al-tn lowtag-mask))
48   ;; FIXME: another 'optimization' which doesn't appear to work:
49   ;; prefetching the hypothetically pointed-to version should help,
50   ;; but this is in fact non-ideal in plenty of ways: we emit way too
51   ;; many of these prefetch instructions; pointed-to objects are very
52   ;; often in the cache anyway; etc. etc.  Still, as proof-of-concept,
53   ;; not too bad.  -- CSR, 2004-07-27
54   (when (member :prefetch *backend-subfeatures*)
55     (inst prefetchnta (make-ea :byte :base value :disp (- lowtag))))
56   (inst cmp al-tn lowtag)
57   (inst jmp (if not-p :ne :e) target))
58
59 (defun %test-headers (value target not-p function-p headers
60                             &optional (drop-through (gen-label)) al-loaded)
61   (let ((lowtag (if function-p fun-pointer-lowtag other-pointer-lowtag)))
62     (multiple-value-bind (equal less-or-equal greater-or-equal when-true when-false)
63         ;; EQUAL, LESS-OR-EQUAL and GREATER-OR-EQUAL are the conditions for
64         ;; branching to TARGET.  WHEN-TRUE and WHEN-FALSE are the
65         ;; labels to branch to when we know it's true and when we know
66         ;; it's false respectively.
67         (if not-p
68             (values :ne :a :b drop-through target)
69             (values :e :na :nb target drop-through))
70       (%test-lowtag value when-false t lowtag al-loaded)
71       (cond
72         ((and (null (cdr headers))
73               (numberp (car headers)))
74          ;; Optimize the common case: referencing the value from memory
75          ;; is slightly smaller than loading it and then doing the
76          ;; comparison.  Doing this for other cases (e.g. range of
77          ;; [BIGNUM-WIDETAG..FOO-WIDETAG]) is also possible, but such
78          ;; opportunities don't come up very often and the code would
79          ;; get pretty hairy...
80          (inst cmp (make-ea :byte :base value :disp (- lowtag)) (car headers))
81          (inst jmp equal target))
82         (t
83          (inst mov al-tn (make-ea :byte :base value :disp (- lowtag)))
84          (do ((remaining headers (cdr remaining)))
85              ((null remaining))
86            (let ((header (car remaining))
87                  (last (null (cdr remaining))))
88              (cond
89                ((atom header)
90                 (cond
91                   ((and (not last) (null (cddr remaining))
92                         (atom (cadr remaining))
93                         (= (logcount (logxor header (cadr remaining))) 1))
94                    ;; BASE-STRING, (VECTOR NIL), BIT-VECTOR, (VECTOR T)
95                    (inst and al-tn (ldb (byte 8 0) (logeqv header (cadr remaining))))
96                    (inst cmp al-tn (ldb (byte 8 0) (logand header (cadr remaining))))
97                    (inst jmp equal target)
98                    (return))
99                   (t
100                    (inst cmp al-tn header)
101                    (if last
102                        (inst jmp equal target)
103                        (inst jmp :e when-true)))))
104                (t
105                 (let ((start (car header))
106                       (end (cdr header)))
107                   (cond
108                     ;; LAST = don't need al-tn later
109                     ((and last (not (= start bignum-widetag))
110                           (= (+ start 4) end) (= (logcount (logxor start end)) 1))
111                      ;; SIMPLE-STRING
112                      (inst and al-tn (ldb (byte 8 0) (logeqv start end)))
113                      (inst cmp al-tn (ldb (byte 8 0) (logand start end)))
114                      (inst jmp equal target))
115                     ((and (not last) (null (cddr remaining))
116                           (= (+ start 4) end) (= (logcount (logxor start end)) 1)
117                           (listp (cadr remaining))
118                           (= (+ (caadr remaining) 4) (cdadr remaining))
119                           (= (logcount (logxor (caadr remaining) (cdadr remaining))) 1)
120                           (= (logcount (logxor (caadr remaining) start)) 1))
121                      ;; STRING
122                      (inst and al-tn (ldb (byte 8 0) (logeqv start (cdadr remaining))))
123                      (inst cmp al-tn (ldb (byte 8 0) (logand start (cdadr remaining))))
124                      (inst jmp equal target)
125                      ;; we've shortcircuited the DO, so we must return.
126                      ;; It's OK to do so, because (NULL (CDDR REMAINING))
127                      ;; was true.
128                      (return))
129                     (t
130                      (unless (= start bignum-widetag)
131                        (inst cmp al-tn start)
132                        (if (= end complex-array-widetag)
133                            (progn
134                              (aver last)
135                              (inst jmp greater-or-equal target))
136                            (inst jmp :b when-false))) ; was :l
137                      (unless (= end complex-array-widetag)
138                        (inst cmp al-tn end)
139                        (if last
140                            (inst jmp less-or-equal target)
141                            (inst jmp :be when-true)))))))))))) ; was :le
142       (emit-label drop-through))))
143 \f
144 ;;;; type checking and testing
145
146 (define-vop (check-type)
147   (:args (value :target result :scs (any-reg descriptor-reg)))
148   (:results (result :scs (any-reg descriptor-reg)))
149   (:temporary (:sc unsigned-reg :offset eax-offset :to (:result 0)) eax)
150   (:ignore eax)
151   (:vop-var vop)
152   (:save-p :compute-only))
153
154 (define-vop (type-predicate)
155   (:args (value :scs (any-reg descriptor-reg)))
156   (:temporary (:sc unsigned-reg :offset eax-offset) eax)
157   (:ignore eax)
158   (:conditional)
159   (:info target not-p)
160   (:policy :fast-safe))
161
162 ;;; simpler VOP that don't need a temporary register
163 (define-vop (simple-check-type)
164   (:args (value :target result :scs (any-reg descriptor-reg)))
165   (:results (result :scs (any-reg descriptor-reg)
166                     :load-if (not (and (sc-is value any-reg descriptor-reg)
167                                        (sc-is result control-stack)))))
168   (:vop-var vop)
169   (:save-p :compute-only))
170
171 (define-vop (simple-type-predicate)
172   (:args (value :scs (any-reg descriptor-reg control-stack)))
173   (:conditional)
174   (:info target not-p)
175   (:policy :fast-safe))
176
177 (defun cost-to-test-types (type-codes)
178   (+ (* 2 (length type-codes))
179      (if (> (apply #'max type-codes) lowtag-limit) 7 2)))
180
181 (defmacro !define-type-vops (pred-name check-name ptype error-code
182                              (&rest type-codes)
183                              &key (variant nil variant-p) &allow-other-keys)
184   ;; KLUDGE: UGH. Why do we need this eval? Can't we put this in the
185   ;; expansion?
186   (let* ((cost (cost-to-test-types (mapcar #'eval type-codes)))
187          (prefix (if variant-p
188                      (concatenate 'string (string variant) "-")
189                      "")))
190     `(progn
191        ,@(when pred-name
192            `((define-vop (,pred-name ,(intern (concatenate 'string prefix "TYPE-PREDICATE")))
193                (:translate ,pred-name)
194                (:generator ,cost
195                  (test-type value target not-p (,@type-codes))))))
196        ,@(when check-name
197            `((define-vop (,check-name ,(intern (concatenate 'string prefix "CHECK-TYPE")))
198                (:generator ,cost
199                  (let ((err-lab
200                         (generate-error-code vop ',error-code value)))
201                    (test-type value err-lab t (,@type-codes))
202                    (move result value))))))
203        ,@(when ptype
204            `((primitive-type-vop ,check-name (:check) ,ptype))))))
205 \f
206 ;;;; other integer ranges
207
208 (define-vop (fixnump/unsigned-byte-32 simple-type-predicate)
209   (:args (value :scs (unsigned-reg)))
210   (:arg-types unsigned-num)
211   (:translate fixnump)
212   (:generator 5
213     (inst cmp value #.sb!xc:most-positive-fixnum)
214     (inst jmp (if not-p :a :be) target)))
215
216 ;;; A (SIGNED-BYTE 32) can be represented with either fixnum or a bignum with
217 ;;; exactly one digit.
218
219 (define-vop (signed-byte-32-p type-predicate)
220   (:translate signed-byte-32-p)
221   (:generator 45
222     (multiple-value-bind (yep nope)
223         (if not-p
224             (values not-target target)
225             (values target not-target))
226       (generate-fixnum-test value)
227       (inst jmp :e yep)
228       (move eax-tn value)
229       (inst and al-tn lowtag-mask)
230       (inst cmp al-tn other-pointer-lowtag)
231       (inst jmp :ne nope)
232       (loadw eax-tn value 0 other-pointer-lowtag)
233       (inst cmp eax-tn (+ (ash 1 n-widetag-bits) bignum-widetag))
234       (inst jmp (if not-p :ne :e) target))
235     NOT-TARGET))
236
237 (define-vop (check-signed-byte-32 check-type)
238   (:generator 45
239     (let ((nope (generate-error-code vop
240                                      'object-not-signed-byte-32-error
241                                      value)))
242       (generate-fixnum-test value)
243       (inst jmp :e yep)
244       (move eax-tn value)
245       (inst and al-tn lowtag-mask)
246       (inst cmp al-tn other-pointer-lowtag)
247       (inst jmp :ne nope)
248       (loadw eax-tn value 0 other-pointer-lowtag)
249       (inst cmp eax-tn (+ (ash 1 n-widetag-bits) bignum-widetag))
250       (inst jmp :ne nope))
251     YEP
252     (move result value)))
253
254 ;;; An (unsigned-byte 32) can be represented with either a positive
255 ;;; fixnum, a bignum with exactly one positive digit, or a bignum with
256 ;;; exactly two digits and the second digit all zeros.
257 (define-vop (unsigned-byte-32-p type-predicate)
258   (:translate unsigned-byte-32-p)
259   (:generator 45
260     (let ((not-target (gen-label))
261           (single-word (gen-label))
262           (fixnum (gen-label)))
263       (multiple-value-bind (yep nope)
264           (if not-p
265               (values not-target target)
266               (values target not-target))
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 (if not-p :s :ns) target)
299
300         (emit-label not-target)))))
301
302 (define-vop (check-unsigned-byte-32 check-type)
303   (:generator 45
304     (let ((nope
305            (generate-error-code vop 'object-not-unsigned-byte-32-error value))
306           (yep (gen-label))
307           (fixnum (gen-label))
308           (single-word (gen-label)))
309
310       ;; Is it a fixnum?
311       (generate-fixnum-test value)
312       (move eax-tn value)
313       (inst jmp :e fixnum)
314
315       ;; If not, is it an other pointer?
316       (inst and al-tn lowtag-mask)
317       (inst cmp al-tn other-pointer-lowtag)
318       (inst jmp :ne nope)
319       ;; Get the header.
320       (loadw eax-tn value 0 other-pointer-lowtag)
321       ;; Is it one?
322       (inst cmp eax-tn (+ (ash 1 n-widetag-bits) bignum-widetag))
323       (inst jmp :e single-word)
324       ;; If it's other than two, we can't be an (unsigned-byte 32)
325       (inst cmp eax-tn (+ (ash 2 n-widetag-bits) bignum-widetag))
326       (inst jmp :ne nope)
327       ;; Get the second digit.
328       (loadw eax-tn value (1+ bignum-digits-offset) other-pointer-lowtag)
329       ;; All zeros, its an (unsigned-byte 32).
330       (inst or eax-tn eax-tn)
331       (inst jmp :z yep)
332       (inst jmp nope)
333
334       (emit-label single-word)
335       ;; Get the single digit.
336       (loadw eax-tn value bignum-digits-offset other-pointer-lowtag)
337
338       ;; positive implies (unsigned-byte 32).
339       (emit-label fixnum)
340       (inst or eax-tn eax-tn)
341       (inst jmp :s nope)
342
343       (emit-label yep)
344       (move result value))))
345 \f
346 ;;;; list/symbol types
347 ;;;
348 ;;; symbolp (or symbol (eq nil))
349 ;;; consp (and list (not (eq nil)))
350
351 (define-vop (symbolp type-predicate)
352   (:translate symbolp)
353   (:generator 12
354     (let ((is-symbol-label (if not-p drop-thru target)))
355       (inst cmp value nil-value)
356       (inst jmp :e is-symbol-label)
357       (test-type value target not-p (symbol-header-widetag)))
358     DROP-THRU))
359
360 (define-vop (check-symbol check-type)
361   (:generator 12
362     (let ((error (generate-error-code vop 'object-not-symbol-error value)))
363       (inst cmp value nil-value)
364       (inst jmp :e drop-thru)
365       (test-type value error t (symbol-header-widetag)))
366     DROP-THRU
367     (move result value)))
368
369 (define-vop (consp type-predicate)
370   (:translate consp)
371   (:generator 8
372     (let ((is-not-cons-label (if not-p target drop-thru)))
373       (inst cmp value nil-value)
374       (inst jmp :e is-not-cons-label)
375       (test-type value target not-p (list-pointer-lowtag)))
376     DROP-THRU))
377
378 (define-vop (check-cons check-type)
379   (:generator 8
380     (let ((error (generate-error-code vop 'object-not-cons-error value)))
381       (inst cmp value nil-value)
382       (inst jmp :e error)
383       (test-type value error t (list-pointer-lowtag))
384       (move result value))))