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