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