b59bd3b843a56c83592849181f9cf54f377afd35
[sbcl.git] / src / code / cross-type.lisp
1 ;;;; cross-compiler-only versions of TYPEP, TYPE-OF, and related functions
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!KERNEL")
13
14 ;;; Is X a fixnum in the target Lisp?
15 (defun fixnump (x)
16   (and (integerp x)
17        (<= sb!vm:*target-most-negative-fixnum*
18            x
19            sb!vm:*target-most-positive-fixnum*)))
20
21 ;;; (This was a useful warning when trying to get bootstrapping
22 ;;; to work, but it's mostly irrelevant noise now that the system
23 ;;; works.)
24 (define-condition cross-type-style-warning (style-warning)
25   ((call :initarg :call
26          :reader cross-type-style-warning-call)
27    (message :reader cross-type-style-warning-message
28             #+cmu :initarg #+cmu :message ; (to stop bogus non-STYLE WARNING)
29             ))
30   (:report (lambda (c s)
31              (format
32               s
33               "cross-compilation-time type ambiguity (should be OK) in ~S:~%~A"
34               (cross-type-style-warning-call c)
35               (cross-type-style-warning-message c)))))
36
37 ;;; This warning is issued when giving up on a type calculation where a
38 ;;; conservative answer is acceptable. Since a conservative answer is
39 ;;; acceptable, the only downside is lost optimization opportunities.
40 (define-condition cross-type-giving-up-conservatively
41     (cross-type-style-warning)
42   ((message :initform "giving up conservatively"
43             #+cmu :reader #+cmu #.(gensym) ; (to stop bogus non-STYLE WARNING)
44             )))
45
46 ;;; This warning refers to the flexibility in the ANSI spec with
47 ;;; regard to run-time distinctions between floating point types.
48 ;;; (E.g. the cross-compilation host might not even distinguish
49 ;;; between SINGLE-FLOAT and DOUBLE-FLOAT, so a DOUBLE-FLOAT number
50 ;;; would test positive as SINGLE-FLOAT.) If the target SBCL does make
51 ;;; this distinction, then information is lost. It's not too hard to
52 ;;; contrive situations where this would be a problem. In practice we
53 ;;; don't tend to run into them because all widely used Common Lisp
54 ;;; environments do recognize the distinction between SINGLE-FLOAT and
55 ;;; DOUBLE-FLOAT, and we don't really need the other distinctions
56 ;;; (e.g. between SHORT-FLOAT and SINGLE-FLOAT), so we call
57 ;;; WARN-POSSIBLE-CROSS-TYPE-FLOAT-INFO-LOSS to test at runtime
58 ;;; whether we need to worry about this at all, and not warn unless we
59 ;;; do. If we *do* have to worry about this at runtime, my (WHN
60 ;;; 19990808) guess is that the system will break in multiple places,
61 ;;; so this is a real WARNING, not just a STYLE-WARNING.
62 ;;;
63 ;;; KLUDGE: If we ever try to support LONG-FLOAT or SHORT-FLOAT, this
64 ;;; situation will get a lot more complicated.
65 (defun warn-possible-cross-type-float-info-loss (call)
66   (when (or (subtypep 'single-float 'double-float)
67             (subtypep 'double-float 'single-float))
68     (warn "possible floating point information loss in ~S" call)))
69
70 (defun sb!xc:type-of (object)
71   (labels (;; FIXME: This function is a no-op now that we no longer
72            ;; have a distinct package T%CL to translate
73            ;; for-the-target-Lisp CL symbols to, and should go away
74            ;; completely.
75            (translate (expr) expr))
76     (let ((raw-result (type-of object)))
77       (cond ((or (subtypep raw-result 'float)
78                  (subtypep raw-result 'complex))
79              (warn-possible-cross-type-float-info-loss
80               `(sb!xc:type-of ,object))
81              (translate raw-result))
82             ((subtypep raw-result 'integer)
83              (cond ((<= 0 object 1)
84                     'bit)
85                    ((fixnump object)
86                     'fixnum)
87                    (t
88                     'integer)))
89             ((some (lambda (type) (subtypep raw-result type))
90                    '(array character list symbol))
91              (translate raw-result))
92             (t
93              (error "can't handle TYPE-OF ~S in cross-compilation"))))))
94
95 ;;; Is SYMBOL in the CL package? Note that we're testing this on the
96 ;;; cross-compilation host, which could do things any old way. In
97 ;;; particular, it might be in the CL package even though
98 ;;; SYMBOL-PACKAGE is not (FIND-PACKAGE :CL). So we test things
99 ;;; another way.
100 (defun in-cl-package-p (symbol)
101   (eql (find-symbol (symbol-name symbol) :cl)
102        symbol))
103
104 ;;; This is like TYPEP, except that it asks whether HOST-OBJECT would
105 ;;; be of TARGET-TYPE when instantiated on the target SBCL. Since this
106 ;;; is hard to determine in some cases, and since in other cases we
107 ;;; just haven't bothered to try, it needs to return two values, just
108 ;;; like SUBTYPEP: the first value for its conservative opinion (never
109 ;;; T unless it's certain) and the second value to tell whether it's
110 ;;; certain.
111 (defun cross-typep (host-object raw-target-type)
112   (let ((target-type (type-expand raw-target-type)))
113     (flet ((warn-and-give-up ()
114            ;; We don't have to keep track of this as long as system
115            ;; performance is acceptable, since giving up
116            ;; conservatively is a safe way out.
117            #+nil
118            (warn 'cross-type-giving-up-conservatively
119                  :call `(cross-typep ,host-object ,raw-target-type))
120            (values nil nil))
121            (warn-about-possible-float-info-loss ()
122              (warn-possible-cross-type-float-info-loss
123                `(cross-typep ,host-object ,raw-target-type)))
124            ;; a convenient idiom for making more matches to special cases:
125            ;; Test both forms of target type for membership in LIST.
126            ;;
127            ;; (In order to avoid having to use too much deep knowledge
128            ;; of types, it's sometimes convenient to test RAW-TARGET-TYPE
129            ;; as well as the expanded type, since we can get matches with
130            ;; just EQL. E.g. SIMPLE-STRING can be matched with EQL, while
131            ;; safely matching its expansion,
132            ;;  (OR (SIMPLE-ARRAY CHARACTER (*)) (SIMPLE-BASE-STRING *))
133            ;; would require logic clever enough to know that, e.g., OR is
134            ;; commutative.)
135            (target-type-is-in (list)
136              (or (member raw-target-type list)
137                  (member target-type list))))
138       (cond (;; Handle various SBCL-specific types which can't exist on
139              ;; the ANSI cross-compilation host. KLUDGE: This code will
140              ;; need to be tweaked by hand if the names of these types
141              ;; ever change, ugh!
142              (if (consp target-type)
143                  (member (car target-type)
144                          '(sb!alien:alien))
145                  (member target-type
146                          '(system-area-pointer
147                            funcallable-instance
148                            sb!alien-internals:alien-value)))
149              (values nil t))
150             (;; special case when TARGET-TYPE isn't a type spec, but
151              ;; instead a CLASS object
152              (typep target-type 'sb!xc::structure-class)
153              ;; SBCL-specific types which have an analogue specially
154              ;; created on the host system
155              (if (sb!xc:subtypep (sb!xc:class-name target-type)
156                                  'sb!kernel::structure!object)
157                  (values (typep host-object (sb!xc:class-name target-type)) t)
158                  (values nil t)))
159             ((and (symbolp target-type)
160                   (find-class target-type nil)
161                   (subtypep target-type 'sb!kernel::structure!object))
162              (values (typep host-object target-type) t))
163             ((and (symbolp target-type)
164                   (sb!xc:find-class target-type nil)
165                   (sb!xc:subtypep target-type 'cl:structure-object)
166                   (typep host-object '(or symbol number list character)))
167              (values nil t))
168             (;; easy cases of arrays and vectors
169              (target-type-is-in
170               '(array simple-string simple-vector string vector))
171              (values (typep host-object target-type) t))
172             (;; general cases of vectors
173              (and (not (unknown-type-p (values-specifier-type target-type)))
174                   (sb!xc:subtypep target-type 'cl:vector))
175              (if (vectorp host-object)
176                  (warn-and-give-up) ; general-case vectors being way too hard
177                  (values nil t))) ; but "obviously not a vector" being easy
178             (;; general cases of arrays
179              (and (not (unknown-type-p (values-specifier-type target-type)))
180                   (sb!xc:subtypep target-type 'cl:array))
181              (if (arrayp host-object)
182                  (warn-and-give-up) ; general-case arrays being way too hard
183                  (values nil t))) ; but "obviously not an array" being easy
184             ((target-type-is-in '(*))
185              ;; KLUDGE: SBCL has * as an explicit wild type. While
186              ;; this is sort of logical (because (e.g. (ARRAY * 1)) is
187              ;; a valid type) it's not ANSI: looking at the ANSI
188              ;; definitions of complex types like like ARRAY shows
189              ;; that they consider * different from other type names.
190              ;; Someday we should probably get rid of this non-ANSIism
191              ;; in base SBCL, but until we do, we might as well here
192              ;; in the cross compiler. And in order to make sure that
193              ;; we don't continue doing it after we someday patch
194              ;; SBCL's type system so that * is no longer a type, we
195              ;; make this assertion. -- WHN 2001-08-08
196              (aver (typep (specifier-type '*) 'named-type))
197              (values t t))
198             (;; Many simple types are guaranteed to correspond exactly
199              ;; between any host ANSI Common Lisp and the target
200              ;; Common Lisp. (Some array types are too, but they
201              ;; were picked off earlier.)
202              (target-type-is-in
203               '(bit character complex cons float function integer keyword
204                     list nil null number rational real signed-byte symbol t
205                     unsigned-byte))
206              (values (typep host-object target-type) t))
207             (;; Floating point types are guaranteed to correspond,
208              ;; too, but less exactly.
209              (target-type-is-in
210               '(single-float double-float))
211              (cond ((floatp host-object)
212                     (warn-about-possible-float-info-loss)
213                     (values (typep host-object target-type) t))
214                    (t
215                     (values nil t))))
216             ;; Some types require translation between the cross-compilation
217             ;; host Common Lisp and the target SBCL.
218             ((target-type-is-in '(sb!xc:class))
219              (values (typep host-object 'sb!xc:class) t))
220             ((target-type-is-in '(fixnum))
221              (values (fixnump host-object) t))
222             ;; Some types are too hard to handle in the positive
223             ;; case, but at least we can be confident in a large
224             ;; fraction of the negative cases..
225             ((target-type-is-in
226               '(base-string simple-base-string simple-string))
227              (if (stringp host-object)
228                  (warn-and-give-up)
229                  (values nil t)))
230             ((target-type-is-in '(character base-char))
231              (cond ((typep host-object 'standard-char)
232                     (values t t))
233                    ((not (characterp host-object))
234                     (values nil t))
235                    (t
236                     (warn-and-give-up))))
237             ((target-type-is-in '(stream instance))
238              ;; Neither target CL:STREAM nor target SB!KERNEL:INSTANCE
239              ;; is implemented as a STRUCTURE-OBJECT, so they'll fall
240              ;; through the tests above. We don't want to assume too
241              ;; much about them here, but at least we know enough
242              ;; about them to say that neither T nor NIL nor indeed
243              ;; any other symbol in the cross-compilation host is one.
244              ;; That knowledge suffices to answer so many of the
245              ;; questions that the cross-compiler asks that it's well
246              ;; worth special-casing it here.
247              (if (symbolp host-object)
248                  (values nil t)
249                  (warn-and-give-up)))
250             ;; various hacks for composite types..
251             ((consp target-type)
252              (let ((first (first target-type))
253                    (rest (rest target-type)))
254                (case first
255                  ;; Many complex types are guaranteed to correspond exactly
256                  ;; between any host ANSI Common Lisp and the target SBCL.
257                  ((integer member mod rational real signed-byte unsigned-byte)
258                   (values (typep host-object target-type) t))
259                  ;; Floating point types are guaranteed to correspond,
260                  ;; too, but less exactly.
261                  ((single-float double-float)
262                   (cond ((floatp host-object)
263                          (warn-about-possible-float-info-loss)
264                          (values (typep host-object target-type) t))
265                         (t
266                          (values nil t))))
267                  ;; Some complex types have translations that are less
268                  ;; trivial.
269                  (and (every/type #'cross-typep host-object rest))
270                  (or  (any/type   #'cross-typep host-object rest))
271                  ;; If we want to work with the KEYWORD type, we need
272                  ;; to grok (SATISFIES KEYWORDP).
273                  (satisfies
274                   (destructuring-bind (predicate-name) rest
275                     (if (and (in-cl-package-p predicate-name)
276                              (fboundp predicate-name))
277                         ;; Many things like KEYWORDP, ODDP, PACKAGEP,
278                         ;; and NULL correspond between host and target.
279                         (values (not (null (funcall predicate-name
280                                                     host-object)))
281                                 t)
282                         ;; For symbols not in the CL package, it's not
283                         ;; in general clear how things correspond
284                         ;; between host and target, so we punt.
285                         (warn-and-give-up))))
286                  ;; Some complex types are too hard to handle in the
287                  ;; positive case, but at least we can be confident in
288                  ;; a large fraction of the negative cases..
289                  ((base-string simple-base-string simple-string)
290                   (if (stringp host-object)
291                       (warn-and-give-up)
292                       (values nil t)))
293                  ((vector simple-vector)
294                   (if (vectorp host-object)
295                       (warn-and-give-up)
296                       (values nil t)))
297                  ((array simple-array)
298                   (if (arrayp host-object)
299                       (warn-and-give-up)
300                       (values nil t)))
301                  (function
302                   (if (functionp host-object)
303                       (warn-and-give-up)
304                       (values nil t)))
305                  ;; And the Common Lisp type system is complicated,
306                  ;; and we don't try to implement everything.
307                  (otherwise (warn-and-give-up)))))
308             ;; And the Common Lisp type system is complicated, and
309             ;; we don't try to implement everything.
310             (t
311              (warn-and-give-up))))))
312
313 ;;; This is an incomplete TYPEP which runs at cross-compile time to
314 ;;; tell whether OBJECT is the host Lisp representation of a target
315 ;;; SBCL type specified by TARGET-TYPE-SPEC. It need make no pretense
316 ;;; to completeness, since it need only handle the cases which arise
317 ;;; when building SBCL itself, e.g. testing that range limits FOO and
318 ;;; BAR in (INTEGER FOO BAR) are INTEGERs.
319 (defun sb!xc:typep (host-object target-type-spec &optional (env nil env-p))
320   (declare (ignore env))
321   (aver (null env-p)) ; 'cause we're too lazy to think about it
322   (multiple-value-bind (opinion certain-p)
323       (cross-typep host-object target-type-spec)
324     ;; A program that calls TYPEP doesn't want uncertainty and
325     ;; probably can't handle it.
326     (if certain-p
327         opinion
328         (error "uncertain in SB!XC:TYPEP ~S ~S"
329                host-object
330                target-type-spec))))
331
332 ;;; This is an incomplete, portable implementation for use at
333 ;;; cross-compile time only.
334 (defun ctypep (obj ctype)
335   (check-type ctype ctype)
336   (let (;; the Common Lisp type specifier corresponding to CTYPE
337         (type (type-specifier ctype)))
338     (check-type type (or symbol cons))
339     (cross-typep obj type)))
340
341 (defparameter *universal-function-type*
342   (make-function-type :wild-args t
343                       :returns *wild-type*))
344
345 (defun ctype-of (x)
346   (typecase x
347     (function
348      (if (typep x 'generic-function)
349          ;; Since at cross-compile time we build a CLOS-free bootstrap
350          ;; version of SBCL, it's unclear how to explain to it what a
351          ;; generic function is.
352          (error "not implemented: cross CTYPE-OF generic function")
353          ;; There's no ANSI way to find out what the function is
354          ;; declared to be, so we just return the CTYPE for the
355          ;; most-general function.
356          *universal-function-type*))
357     (symbol
358      (make-member-type :members (list x)))
359     (number
360      (ctype-of-number x))
361     (array
362      (let ((etype (specifier-type (array-element-type x))))
363        (make-array-type :dimensions (array-dimensions x)
364                         :complexp (not (typep x 'simple-array))
365                         :element-type etype
366                         :specialized-element-type etype)))
367     (cons (specifier-type 'cons))
368     (character
369      (cond ((typep x 'standard-char)
370             ;; (Note that SBCL doesn't distinguish between BASE-CHAR and
371             ;; CHARACTER.)
372             (sb!xc:find-class 'base-char))
373            ((not (characterp x))
374             nil)
375            (t
376             ;; Beyond this, there seems to be no portable correspondence.
377             (error "can't map host Lisp CHARACTER ~S to target Lisp" x))))
378     (structure!object
379      (sb!xc:find-class (uncross (class-name (class-of x)))))
380     (t
381      ;; There might be more cases which we could handle with
382      ;; sufficient effort; since all we *need* to handle are enough
383      ;; cases for bootstrapping, we don't try to be complete here,. If
384      ;; future maintainers make the bootstrap code more complicated,
385      ;; they can also add new cases here to handle it. -- WHN 2000-11-11
386      (error "can't handle ~S in cross CTYPE-OF" x))))