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