0.6.11.26:
[sbcl.git] / src / code / early-type.lisp
1 ;;;; This software is part of the SBCL system. See the README file for
2 ;;;; more information.
3 ;;;;
4 ;;;; This software is derived from the CMU CL system, which was
5 ;;;; written at Carnegie Mellon University and released into the
6 ;;;; public domain. The software is in the public domain and is
7 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
8 ;;;; files for more information.
9
10 (in-package "SB!KERNEL")
11
12 (!begin-collecting-cold-init-forms)
13
14 ;;; Has the type system been properly initialized? (I.e. is it OK to
15 ;;; use it?)
16 (defvar *type-system-initialized* #+sb-xc-host nil) ; (set in cold load)
17 \f
18 ;;; Return the type structure corresponding to a type specifier. We
19 ;;; pick off structure types as a special case.
20 ;;;
21 ;;; Note: VALUES-SPECIFIER-TYPE-CACHE-CLEAR must be called whenever a
22 ;;; type is defined (or redefined).
23 (defun-cached (values-specifier-type
24                :hash-function (lambda (x)
25                                 ;; FIXME: The THE FIXNUM stuff is
26                                 ;; redundant in SBCL (or modern CMU
27                                 ;; CL) because of type inference.
28                                 (the fixnum
29                                      (logand (the fixnum (sxhash x))
30                                              #x3FF)))
31                :hash-bits 10
32                :init-wrapper !cold-init-forms)
33               ((orig eq))
34   (let ((u (uncross orig)))
35     (or (info :type :builtin u)
36         (let ((spec (type-expand u)))
37           (cond
38            ((and (not (eq spec u))
39                  (info :type :builtin spec)))
40            ((eq (info :type :kind spec) :instance)
41             (sb!xc:find-class spec))
42            ((typep spec 'class)
43             ;; There doesn't seem to be any way to translate
44             ;; (TYPEP SPEC 'BUILT-IN-CLASS) into something which can be
45             ;; executed on the host Common Lisp at cross-compilation time.
46             #+sb-xc-host (error
47                           "stub: (TYPEP SPEC 'BUILT-IN-CLASS) on xc host")
48             (if (typep spec 'built-in-class)
49                 (or (built-in-class-translation spec) spec)
50                 spec))
51            (t
52             (let* (;; FIXME: This automatic promotion of FOO-style
53                    ;; specs to (FOO)-style specs violates the ANSI
54                    ;; standard. Unfortunately, we can't fix the
55                    ;; problem just by removing it, since then things
56                    ;; downstream should break. But at some point we
57                    ;; should fix this and the things downstream too.
58                    (lspec (if (atom spec) (list spec) spec))
59                    (fun (info :type :translator (car lspec))))
60               (cond (fun
61                      (funcall fun lspec))
62                     ((or (and (consp spec) (symbolp (car spec)))
63                          (symbolp spec))
64                      (when *type-system-initialized*
65                        (signal 'parse-unknown-type :specifier spec))
66                      ;; (The RETURN-FROM here inhibits caching.)
67                      (return-from values-specifier-type
68                        (make-unknown-type :specifier spec)))
69                     (t
70                      (error "bad thing to be a type specifier: ~S"
71                             spec))))))))))
72
73 ;;; Like VALUES-SPECIFIER-TYPE, except that we guarantee to never
74 ;;; return a VALUES type.
75 (defun specifier-type (x)
76   (let ((res (values-specifier-type x)))
77     (when (values-type-p res)
78       (error "VALUES type illegal in this context:~%  ~S" x))
79     res))
80
81 ;;; Similar to MACROEXPAND, but expands DEFTYPEs. We don't bother
82 ;;; returning a second value.
83 (defun type-expand (form)
84   (let ((def (cond ((symbolp form)
85                     (info :type :expander form))
86                    ((and (consp form) (symbolp (car form)))
87                     (info :type :expander (car form)))
88                    (t nil))))
89     (if def
90         (type-expand (funcall def (if (consp form) form (list form))))
91         form)))
92
93 ;;; A HAIRY-TYPE represents anything too weird to be described
94 ;;; reasonably or to be useful, such as NOT, SATISFIES, unknown types,
95 ;;; and unreasonably complicated types involving AND. We just remember
96 ;;; the original type spec.
97 (defstruct (hairy-type (:include ctype
98                                  (class-info (type-class-or-lose 'hairy))
99                                  (enumerable t))
100                        (:copier nil)
101                        #!+cmu (:pure nil))
102   ;; the Common Lisp type-specifier
103   (specifier nil :type t))
104
105 (!define-type-class hairy)
106
107 ;;; An UNKNOWN-TYPE is a type not known to the type system (not yet
108 ;;; defined). We make this distinction since we don't want to complain
109 ;;; about types that are hairy but defined.
110 (defstruct (unknown-type (:include hairy-type)
111                          (:copier nil)))
112
113 ;;; ARGS-TYPE objects are used both to represent VALUES types and
114 ;;; to represent FUNCTION types.
115 (defstruct (args-type (:include ctype)
116                       (:constructor nil)
117                       (:copier nil))
118   ;; Lists of the type for each required and optional argument.
119   (required nil :type list)
120   (optional nil :type list)
121   ;; The type for the rest arg. NIL if there is no rest arg.
122   (rest nil :type (or ctype null))
123   ;; true if &KEY arguments are specified
124   (keyp nil :type boolean)
125   ;; list of KEY-INFO structures describing the &KEY arguments
126   (keywords nil :type list)
127   ;; true if other &KEY arguments are allowed
128   (allowp nil :type boolean))
129
130 (defstruct (values-type
131             (:include args-type
132                       (class-info (type-class-or-lose 'values)))
133             (:copier nil)))
134
135 (!define-type-class values)
136
137 (defstruct (function-type
138             (:include args-type
139                       (class-info (type-class-or-lose 'function))))
140   ;; True if the arguments are unrestrictive, i.e. *.
141   (wild-args nil :type boolean)
142   ;; Type describing the return values. This is a values type
143   ;; when multiple values were specified for the return.
144   (returns (required-argument) :type ctype))
145
146 ;;; The CONSTANT-TYPE structure represents a use of the
147 ;;; CONSTANT-ARGUMENT "type specifier", which is only meaningful in
148 ;;; function argument type specifiers used within the compiler. (It
149 ;;; represents something that the compiler knows to be a constant.)
150 (defstruct (constant-type
151             (:include ctype
152                       (class-info (type-class-or-lose 'constant)))
153             (:copier nil))
154   ;; The type which the argument must be a constant instance of for this type
155   ;; specifier to win.
156   (type (required-argument) :type ctype))
157
158 ;;; The NAMED-TYPE is used to represent *, T and NIL. These types must be
159 ;;; super- or sub-types of all types, not just classes and * and NIL aren't
160 ;;; classes anyway, so it wouldn't make much sense to make them built-in
161 ;;; classes.
162 (defstruct (named-type (:include ctype
163                                  (class-info (type-class-or-lose 'named)))
164                        (:copier nil))
165   (name nil :type symbol))
166
167 ;;; a list of all the float "formats" (i.e. internal representations;
168 ;;; nothing to do with #'FORMAT), in order of decreasing precision
169 (eval-when (:compile-toplevel :load-toplevel :execute)
170   (defparameter *float-formats*
171     '(long-float double-float single-float short-float)))
172
173 ;;; The type of a float format.
174 (deftype float-format () `(member ,@*float-formats*))
175
176 ;;; A NUMERIC-TYPE represents any numeric type, including things
177 ;;; such as FIXNUM.
178 (defstruct (numeric-type (:include ctype
179                                    (class-info (type-class-or-lose 'number)))
180                          (:constructor %make-numeric-type)
181                          (:copier nil))
182   ;; the kind of numeric type we have, or NIL if not specified (just
183   ;; NUMBER or COMPLEX)
184   ;;
185   ;; KLUDGE: A slot named CLASS for a non-CLASS value is bad.
186   ;; Especially when a CLASS value *is* stored in another slot (called
187   ;; CLASS-INFO:-). Perhaps this should be called CLASS-NAME? Also
188   ;; weird that comment above says "Numeric-Type is used to represent
189   ;; all numeric types" but this slot doesn't allow COMPLEX as an
190   ;; option.. how does this fall into "not specified" NIL case above?
191   ;; Perhaps someday we can switch to CLOS and make NUMERIC-TYPE
192   ;; be an abstract base class and INTEGER-TYPE, RATIONAL-TYPE, and
193   ;; whatnot be concrete subclasses..
194   (class nil :type (member integer rational float nil) :read-only t)
195   ;; "format" for a float type (i.e. type specifier for a CPU
196   ;; representation of floating point, e.g. 'SINGLE-FLOAT -- nothing
197   ;; to do with #'FORMAT), or NIL if not specified or not a float.
198   ;; Formats which don't exist in a given implementation don't appear
199   ;; here.
200   (format nil :type (or float-format null) :read-only t)
201   ;; Is this a complex numeric type?  Null if unknown (only in NUMBER).
202   ;;
203   ;; FIXME: I'm bewildered by FOO-P names for things not intended to
204   ;; interpreted as truth values. Perhaps rename this COMPLEXNESS?
205   (complexp :real :type (member :real :complex nil) :read-only t)
206   ;; The upper and lower bounds on the value, or NIL if there is no
207   ;; bound. If a list of a number, the bound is exclusive. Integer
208   ;; types never have exclusive bounds, i.e. they may have them on
209   ;; input, but they're canonicalized to inclusive bounds before we
210   ;; store them here.
211   (low nil :type (or number cons null) :read-only t)
212   (high nil :type (or number cons null) :read-only t))
213
214 ;;; Impose canonicalization rules for NUMERIC-TYPE. Note that in some
215 ;;; cases, despite the name, we return *EMPTY-TYPE* instead of a
216 ;;; NUMERIC-TYPE.
217 (defun make-numeric-type (&key class format (complexp :real) low high
218                                enumerable)
219   ;; if interval is empty
220   (if (and low
221            high
222            (if (or (consp low) (consp high)) ; if either bound is exclusive
223                (>= (type-bound-number low) (type-bound-number high))
224                (> low high)))
225       *empty-type*
226       (multiple-value-bind (canonical-low canonical-high)
227           (case class
228             (integer
229              ;; INTEGER types always have their LOW and HIGH bounds
230              ;; represented as inclusive, not exclusive values.
231              (values (if (consp low)
232                          (1+ (type-bound-number low))
233                          low)
234                      (if (consp high)
235                          (1- (type-bound-number high))
236                          high)))
237             #!+negative-zero-is-not-zero
238             (float
239              ;; Canonicalize a low bound of (-0.0) to 0.0, and a high
240              ;; bound of (+0.0) to -0.0.
241              (values (if (and (consp low)
242                               (floatp (car low))
243                               (zerop (car low))
244                               (minusp (float-sign (car low))))
245                          (float 0.0 (car low))
246                          low)
247                      (if (and (consp high)
248                               (floatp (car high))
249                               (zerop (car high))
250                               (plusp (float-sign (car high))))
251                          (float -0.0 (car high))
252                          high)))
253             (t 
254              ;; no canonicalization necessary
255              (values low high)))
256         (%make-numeric-type :class class
257                             :format format
258                             :complexp complexp
259                             :low canonical-low
260                             :high canonical-high
261                             :enumerable enumerable))))
262
263 (defun modified-numeric-type (base
264                               &key
265                               (class      (numeric-type-class      base))
266                               (format     (numeric-type-format     base))
267                               (complexp   (numeric-type-complexp   base))
268                               (low        (numeric-type-low        base))
269                               (high       (numeric-type-high       base))
270                               (enumerable (numeric-type-enumerable base)))
271   (make-numeric-type :class class
272                      :format format
273                      :complexp complexp
274                      :low low
275                      :high high
276                      :enumerable enumerable))
277
278 ;;; An ARRAY-TYPE is used to represent any array type, including
279 ;;; things such as SIMPLE-STRING.
280 (defstruct (array-type (:include ctype
281                                  (class-info (type-class-or-lose 'array)))
282                        (:copier nil))
283   ;; the dimensions of the array, or * if unspecified. If a dimension
284   ;; is unspecified, it is *.
285   (dimensions '* :type (or list (member *)))
286   ;; Is this not a simple array type? (:MAYBE means that we don't know.)
287   (complexp :maybe :type (member t nil :maybe))
288   ;; the element type as originally specified
289   (element-type (required-argument) :type ctype)
290   ;; the element type as it is specialized in this implementation
291   (specialized-element-type *wild-type* :type ctype))
292
293 ;;; A MEMBER-TYPE represent a use of the MEMBER type specifier. We
294 ;;; bother with this at this level because MEMBER types are fairly
295 ;;; important and union and intersection are well defined.
296 (defstruct (member-type (:include ctype
297                                   (class-info (type-class-or-lose 'member))
298                                   (enumerable t))
299                         (:copier nil)
300                         #-sb-xc-host (:pure nil))
301   ;; the things in the set, with no duplications
302   (members nil :type list))
303
304 ;;; A COMPOUND-TYPE is a type defined out of a set of types, the
305 ;;; common parent of UNION-TYPE and INTERSECTION-TYPE.
306 (defstruct (compound-type (:include ctype)
307                           (:constructor nil)
308                           (:copier nil))
309   (types nil :type list :read-only t))
310
311 ;;; A UNION-TYPE represents a use of the OR type specifier which we
312 ;;; couldn't canonicalize to something simpler. Canonical form:
313 ;;;   1. All possible pairwise simplifications (using the UNION2 type
314 ;;;      methods) have been performed. Thus e.g. there is never more
315 ;;;      than one MEMBER-TYPE component. FIXME: As of sbcl-0.6.11.13,
316 ;;;      this hadn't been fully implemented yet.
317 ;;;   2. There are never any UNION-TYPE components.
318 (defstruct (union-type (:include compound-type
319                                  (class-info (type-class-or-lose 'union)))
320                        (:constructor %make-union-type (enumerable types))
321                        (:copier nil)))
322
323 ;;; An INTERSECTION-TYPE represents a use of the AND type specifier
324 ;;; which we couldn't canonicalize to something simpler. Canonical form:
325 ;;;   1. All possible pairwise simplifications (using the INTERSECTION2
326 ;;;      type methods) have been performed. Thus e.g. there is never more
327 ;;;      than one MEMBER-TYPE component.
328 ;;;   2. There are never any INTERSECTION-TYPE components: we've
329 ;;;      flattened everything into a single INTERSECTION-TYPE object.
330 ;;;   3. There are never any UNION-TYPE components. Either we should
331 ;;;      use the distributive rule to rearrange things so that
332 ;;;      unions contain intersections and not vice versa, or we
333 ;;;      should just punt to using a HAIRY-TYPE.
334 (defstruct (intersection-type (:include compound-type
335                                         (class-info (type-class-or-lose
336                                                      'intersection)))
337                               (:constructor %make-intersection-type
338                                             (enumerable types))
339                               (:copier nil)))
340
341 ;;; Return TYPE converted to canonical form for a situation where the
342 ;;; "type" '* (which SBCL still represents as a type even though ANSI
343 ;;; CL defines it as a related but different kind of placeholder) is
344 ;;; equivalent to type T.
345 (defun type-*-to-t (type)
346   (if (type= type *wild-type*)
347       *universal-type*
348       type))
349
350 ;;; A CONS-TYPE is used to represent a CONS type.
351 (defstruct (cons-type (:include ctype (:class-info (type-class-or-lose 'cons)))
352                       (:constructor
353                        ;; ANSI says that for CAR and CDR subtype
354                        ;; specifiers '* is equivalent to T. In order
355                        ;; to avoid special cases in SUBTYPEP and
356                        ;; possibly elsewhere, we slam all CONS-TYPE
357                        ;; objects into canonical form w.r.t. this
358                        ;; equivalence at creation time.
359                        make-cons-type (car-raw-type
360                                        cdr-raw-type
361                                        &aux
362                                        (car-type (type-*-to-t car-raw-type))
363                                        (cdr-type (type-*-to-t cdr-raw-type))))
364                       (:copier nil))
365   ;; the CAR and CDR element types (to support ANSI (CONS FOO BAR) types)
366   ;;
367   ;; FIXME: Most or all other type structure slots could also be :READ-ONLY.
368   (car-type (required-argument) :type ctype :read-only t)
369   (cdr-type (required-argument) :type ctype :read-only t))
370
371 ;;; Note that the type NAME has been (re)defined, updating the
372 ;;; undefined warnings and VALUES-SPECIFIER-TYPE cache.
373 (defun %note-type-defined (name)
374   (declare (symbol name))
375   (note-name-defined name :type)
376   (when (boundp 'sb!kernel::*values-specifier-type-cache-vector*)
377     (values-specifier-type-cache-clear))
378   (values))
379
380 (!defun-from-collected-cold-init-forms !early-type-cold-init)