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