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