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