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