0.6.11.19:
[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 ;;; 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 ;;; Like TYPEP, but asks whether HOST-OBJECT would be of TARGET-TYPE
96 ;;; when instantiated on the target SBCL. Since this is hard to decide
97 ;;; in some cases, and since in other cases we just haven't bothered
98 ;;; to try, it needs to return two values, just like SUBTYPEP: the
99 ;;; first value for its conservative opinion (never T unless it's
100 ;;; certain) and the second value to tell whether it's certain.
101 (defun cross-typep (host-object target-type)
102   (flet ((warn-and-give-up ()
103            ;; We don't have to keep track of this as long as system performance
104            ;; is acceptable, since giving up conservatively is a safe way out.
105            #+nil
106            (warn 'cross-type-giving-up-conservatively
107                  :call `(cross-typep ,host-object ,target-type))
108            (values nil nil))
109          (warn-about-possible-float-info-loss ()
110            (warn-possible-cross-type-float-info-loss
111             `(cross-typep ,host-object ,target-type))))
112     (cond (;; Handle various SBCL-specific types which can't exist on
113            ;; the ANSI cross-compilation host. KLUDGE: This code will
114            ;; need to be tweaked by hand if the names of these types
115            ;; ever change, ugh!
116            (if (consp target-type)
117                (member (car target-type)
118                        '(sb!alien:alien))
119                (member target-type
120                        '(system-area-pointer
121                          funcallable-instance
122                          sb!alien-internals:alien-value)))
123            (values nil t))
124           (;; special case when TARGET-TYPE isn't a type spec, but
125            ;; instead a CLASS object
126            (typep target-type 'sb!xc::structure-class)
127            ;; SBCL-specific types which have an analogue specially
128            ;; created on the host system
129            (if (sb!xc:subtypep (sb!xc:class-name target-type)
130                                'sb!kernel::structure!object)
131                (values (typep host-object (sb!xc:class-name target-type)) t)
132                (values nil t)))
133           ((and (symbolp target-type)
134                 (find-class target-type nil)
135                 (subtypep target-type 'sb!kernel::structure!object))
136            (values (typep host-object target-type) t))
137           ((and (symbolp target-type)
138                 (sb!xc:find-class target-type nil)
139                 (sb!xc:subtypep target-type 'cl:structure-object)
140                 (typep host-object '(or symbol number list character)))
141            (values nil t))
142           (;; easy cases of arrays and vectors
143            (member target-type
144                    '(array simple-string simple-vector string vector))
145            (values (typep host-object target-type) t))
146           (;; general cases of vectors
147            (and (not (unknown-type-p (values-specifier-type target-type)))
148                 (sb!xc:subtypep target-type 'cl:vector))
149            (if (vectorp host-object)
150                (warn-and-give-up) ; general case of vectors being way too hard
151                (values nil t))) ; but "obviously not a vector" being easy
152           (;; general cases of arrays
153            (and (not (unknown-type-p (values-specifier-type target-type)))
154                 (sb!xc:subtypep target-type 'cl:array))
155            (if (arrayp host-object)
156                (warn-and-give-up) ; general case of arrays being way too hard
157                (values nil t))) ; but "obviously not an array" being easy
158           ((consp target-type)
159            (let ((first (first target-type))
160                  (rest (rest target-type)))
161              (case first
162                ;; Many complex types are guaranteed to correspond exactly
163                ;; between any host ANSI Common Lisp and the target SBCL.
164                ((integer member mod rational real signed-byte unsigned-byte)
165                 (values (typep host-object target-type) t))
166                ;; Floating point types are guaranteed to correspond,
167                ;; too, but less exactly.
168                ((single-float double-float)
169                 (cond ((floatp host-object)
170                        (warn-about-possible-float-info-loss)
171                        (values (typep host-object target-type) t))
172                       (t
173                        (values nil t))))
174                ;; Some complex types have translations that are less
175                ;; trivial.
176                (and (every/type #'cross-typep host-object rest))
177                (or  (any/type   #'cross-typep host-object rest))
178                ;; Some complex types are too hard to handle in the positive
179                ;; case, but at least we can be confident in a large fraction of
180                ;; the negative cases..
181                ((base-string simple-base-string simple-string)
182                 (if (stringp host-object)
183                     (warn-and-give-up)
184                     (values nil t)))
185                ((vector simple-vector)
186                 (if (vectorp host-object)
187                     (warn-and-give-up)
188                     (values nil t)))
189                ((array simple-array)
190                 (if (arrayp host-object)
191                     (warn-and-give-up)
192                     (values nil t)))
193                (function
194                 (if (functionp host-object)
195                     (warn-and-give-up)
196                     (values nil t)))
197                ;; And the Common Lisp type system is complicated, and
198                ;; we don't try to implement everything.
199                (otherwise (warn-and-give-up)))))
200           (t
201            (case target-type
202              ((*)
203               ;; KLUDGE: SBCL has * as an explicit wild type. While this is
204               ;; sort of logical (because (e.g. (ARRAY * 1)) is a valid type)
205               ;; it's not ANSI: looking at the ANSI definitions of complex
206               ;; types like like ARRAY shows that they consider * different
207               ;; from other type names. Someday we should probably get rid of
208               ;; this non-ANSIism in base SBCL, but until we do, we might as
209               ;; well here in the cross compiler. And in order to make sure
210               ;; that we don't continue doing it after we someday patch SBCL's
211               ;; type system so that * is no longer a type, we make this
212               ;; assertion:
213               (assert (typep (specifier-type '*) 'named-type))
214               (values t t))
215              ;; Many simple types are guaranteed to correspond exactly
216              ;; between any host ANSI Common Lisp and the target
217              ;; Common Lisp. (Some array types are too, but they
218              ;; were picked off earlier.)
219              ((bit character complex cons float function integer keyword
220                list nil null number rational real signed-byte symbol t
221                unsigned-byte)
222               (values (typep host-object target-type) t))
223              ;; Floating point types are guaranteed to correspond,
224              ;; too, but less exactly.
225              ((single-float double-float)
226               (cond ((floatp host-object)
227                      (warn-about-possible-float-info-loss)
228                      (values (typep host-object target-type) t))
229                     (t
230                      (values nil t))))
231              ;; Some types require translation between the cross-compilation
232              ;; host Common Lisp and the target SBCL.
233              (sb!xc:class (values (typep host-object 'sb!xc:class) t))
234              (fixnum (values (fixnump host-object) t))
235              ;; Some types are too hard to handle in the positive
236              ;; case, but at least we can be confident in a large
237              ;; fraction of the negative cases..
238              ((base-string simple-base-string simple-string)
239               (if (stringp host-object)
240                   (warn-and-give-up)
241                   (values nil t)))
242              ((character base-char)
243               (cond ((typep host-object 'standard-char)
244                      (values t t))
245                     ((not (characterp host-object))
246                      (values nil t))
247                     (t
248                      (warn-and-give-up))))
249              ((stream instance)
250               ;; Neither target CL:STREAM nor target
251               ;; SB!KERNEL:INSTANCE is implemented as a
252               ;; STRUCTURE-OBJECT, so they'll fall through the tests
253               ;; above. We don't want to assume too much about them
254               ;; here, but at least we know enough about them to say
255               ;; that neither T nor NIL nor indeed any other symbol in
256               ;; the cross-compilation host is one. That knowledge
257               ;; suffices to answer so many of the questions that the
258               ;; cross-compiler asks that it's well worth
259               ;; special-casing it here.
260               (if (symbolp host-object)
261                   (values nil t)
262                   (warn-and-give-up)))
263              ;; And the Common Lisp type system is complicated, and we
264              ;; don't try to implement everything.
265              (otherwise (warn-and-give-up)))))))
266
267 ;;; An incomplete TYPEP which runs at cross-compile time to tell whether OBJECT
268 ;;; is the host Lisp representation of a target SBCL type specified by
269 ;;; TARGET-TYPE-SPEC. It need make no pretense to completeness, since it
270 ;;; need only handle the cases which arise when building SBCL itself, e.g.
271 ;;; testing that range limits FOO and BAR in (INTEGER FOO BAR) are INTEGERs.
272 (defun sb!xc:typep (host-object target-type-spec &optional (env nil env-p))
273   (declare (ignore env))
274   (assert (null env-p)) ; 'cause we're too lazy to think about it
275   (multiple-value-bind (opinion certain-p)
276       (cross-typep host-object target-type-spec)
277     ;; A program that calls TYPEP doesn't want uncertainty and probably
278     ;; can't handle it.
279     (if certain-p
280         opinion
281         (error "uncertain in SB!XC:TYPEP ~S ~S"
282                host-object
283                target-type-spec))))
284
285 ;;; This implementation is an incomplete, portable version for use at
286 ;;; cross-compile time only.
287 (defun ctypep (obj ctype)
288   (check-type ctype ctype)
289   (let (;; the Common Lisp type specifier corresponding to CTYPE
290         (type (type-specifier ctype)))
291     (check-type type (or symbol cons))
292     (cross-typep obj type)))
293
294 (defparameter *universal-function-type*
295   (make-function-type :wild-args t
296                       :returns *wild-type*))
297
298 (defun ctype-of (x)
299   (typecase x
300     (function
301      (if (typep x 'generic-function)
302          ;; Since at cross-compile time we build a CLOS-free bootstrap
303          ;; version of SBCL, it's unclear how to explain to it what a
304          ;; generic function is.
305          (error "not implemented: cross CTYPE-OF generic function")
306          ;; There's no ANSI way to find out what the function is
307          ;; declared to be, so we just return the CTYPE for the
308          ;; most-general function.
309          *universal-function-type*))
310     (symbol
311      (make-member-type :members (list x)))
312     (number
313      (let* ((num (if (complexp x) (realpart x) x))
314             (res (make-numeric-type
315                   :class (etypecase num
316                            (integer 'integer)
317                            (rational 'rational)
318                            (float 'float))
319                   :format (if (floatp num)
320                               (float-format-name num)
321                               nil))))
322        (cond ((complexp x)
323               (setf (numeric-type-complexp res) :complex)
324               (let ((imag (imagpart x)))
325                 (setf (numeric-type-low res) (min num imag))
326                 (setf (numeric-type-high res) (max num imag))))
327              (t
328               (setf (numeric-type-low res) num)
329               (setf (numeric-type-high res) num)))
330        res))
331     (array
332      (let ((etype (specifier-type (array-element-type x))))
333        (make-array-type :dimensions (array-dimensions x)
334                         :complexp (not (typep x 'simple-array))
335                         :element-type etype
336                         :specialized-element-type etype)))
337     (cons (specifier-type 'cons))
338     (character
339      (cond ((typep x 'standard-char)
340             ;; (Note that SBCL doesn't distinguish between BASE-CHAR and
341             ;; CHARACTER.)
342             (sb!xc:find-class 'base-char))
343            ((not (characterp x))
344             nil)
345            (t
346             ;; Beyond this, there seems to be no portable correspondence.
347             (error "can't map host Lisp CHARACTER ~S to target Lisp" x))))
348     (structure!object
349      (sb!xc:find-class (uncross (class-name (class-of x)))))
350     (t
351      ;; There might be more cases which we could handle with
352      ;; sufficient effort; since all we *need* to handle are enough
353      ;; cases for bootstrapping, we don't try to be complete here,. If
354      ;; future maintainers make the bootstrap code more complicated,
355      ;; they can also add new cases here to handle it. -- WHN 2000-11-11
356      (error "can't handle ~S in cross CTYPE-OF" x))))