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