0.8.1.25:
[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 (defun canonicalize-args-type-args (required optional rest)
71   (when (eq rest *empty-type*)
72     ;; or vice-versa?
73     (setq rest nil))
74   (loop with last-not-rest = nil
75         for i from 0
76         for opt in optional
77         do (cond ((eq opt *empty-type*)
78                   (return (values required (subseq optional i) rest)))
79                  ((neq opt rest)
80                   (setq last-not-rest i)))
81         finally (return (values required
82                                 (if last-not-rest
83                                     (subseq optional 0 (1+ last-not-rest))
84                                     nil)
85                                 rest))))
86
87 (defun args-types (lambda-list-like-thing)
88   (multiple-value-bind
89         (required optional restp rest keyp keys allowp auxp aux
90                   morep more-context more-count llk-p)
91       (parse-lambda-list-like-thing lambda-list-like-thing)
92     (declare (ignore aux morep more-context more-count))
93     (when auxp
94       (error "&AUX in a FUNCTION or VALUES type: ~S." lambda-list-like-thing))
95     (let ((required (mapcar #'single-value-specifier-type required))
96           (optional (mapcar #'single-value-specifier-type optional))
97           (rest (when restp (single-value-specifier-type rest)))
98           (keywords
99            (collect ((key-info))
100              (dolist (key keys)
101                (unless (proper-list-of-length-p key 2)
102                  (error "Keyword type description is not a two-list: ~S." key))
103                (let ((kwd (first key)))
104                  (when (find kwd (key-info) :key #'key-info-name)
105                    (error "~@<repeated keyword ~S in lambda list: ~2I~_~S~:>"
106                           kwd lambda-list-like-thing))
107                  (key-info
108                   (make-key-info
109                    :name kwd
110                    :type (single-value-specifier-type (second key))))))
111              (key-info))))
112       (multiple-value-bind (required optional rest)
113           (canonicalize-args-type-args required optional rest)
114         (values required optional rest keyp keywords allowp llk-p)))))
115
116 (defstruct (values-type
117             (:include args-type
118                       (class-info (type-class-or-lose 'values)))
119             (:constructor %make-values-type)
120             (:copier nil)))
121
122 (defun-cached (make-values-type-cached
123                :hash-bits 8
124                :hash-function (lambda (req opt rest allowp)
125                                 (logand (logxor
126                                          (type-list-cache-hash req)
127                                          (type-list-cache-hash opt)
128                                          (if rest
129                                              (type-hash-value rest)
130                                              42)
131                                          (sxhash allowp))
132                                         #xFF)))
133     ((required equal-but-no-car-recursion)
134      (optional equal-but-no-car-recursion)
135      (rest eq)
136      (allowp eq))
137   (%make-values-type :required required
138                      :optional optional
139                      :rest rest
140                      :allowp allowp))
141
142 ;;; FIXME: ANSI VALUES has a short form (without lambda list
143 ;;; keywords), which should be translated into a long one.
144 (defun make-values-type (&key (args nil argsp)
145                          required optional rest allowp)
146   (if argsp
147       (if (eq args '*)
148           *wild-type*
149           (multiple-value-bind (required optional rest keyp keywords allowp
150                                 llk-p)
151               (args-types args)
152             (declare (ignore keywords))
153             (when keyp
154               (error "&KEY appeared in a VALUES type specifier ~S."
155                      `(values ,@args)))
156             (if llk-p
157                 (make-values-type :required required
158                                   :optional optional
159                                   :rest rest
160                                   :allowp allowp)
161                 (make-short-values-type required))))
162       (multiple-value-bind (required optional rest)
163           (canonicalize-args-type-args required optional rest)
164         (cond ((and (null required)
165                     (null optional)
166                     (eq rest *universal-type*))
167                *wild-type*)
168               ((memq *empty-type* required)
169                *empty-type*)
170               (t (make-values-type-cached required optional
171                                           rest allowp))))))
172
173 (!define-type-class values)
174
175 ;;; (SPECIFIER-TYPE 'FUNCTION) and its subtypes
176 (defstruct (fun-type (:include args-type
177                                (class-info (type-class-or-lose 'function)))
178                      (:constructor
179                       %make-fun-type (&key required optional rest
180                                            keyp keywords allowp
181                                            wild-args
182                                            returns
183                                       &aux (rest (if (eq rest *empty-type*)
184                                                      nil
185                                                      rest)))))
186   ;; true if the arguments are unrestrictive, i.e. *
187   (wild-args nil :type boolean)
188   ;; type describing the return values. This is a values type
189   ;; when multiple values were specified for the return.
190   (returns (missing-arg) :type ctype))
191 (defun make-fun-type (&rest initargs
192                       &key (args nil argsp) returns &allow-other-keys)
193   (if argsp
194       (if (eq args '*)
195           (if (eq returns *wild-type*)
196               (specifier-type 'function)
197               (%make-fun-type :wild-args t :returns returns))
198           (multiple-value-bind (required optional rest keyp keywords allowp)
199               (args-types args)
200             (if (and (null required)
201                      (null optional)
202                      (eq rest *universal-type*)
203                      (not keyp))
204                 (if (eq returns *wild-type*)
205                     (specifier-type 'function)
206                     (%make-fun-type :wild-args t :returns returns))
207                 (%make-fun-type :required required
208                                 :optional optional
209                                 :rest rest
210                                 :keyp keyp
211                                 :keywords keywords
212                                 :allowp allowp
213                                 :returns returns))))
214       ;; FIXME: are we really sure that we won't make something that
215       ;; looks like a completely wild function here?
216       (apply #'%make-fun-type initargs)))
217
218 ;;; The CONSTANT-TYPE structure represents a use of the CONSTANT-ARG
219 ;;; "type specifier", which is only meaningful in function argument
220 ;;; type specifiers used within the compiler. (It represents something
221 ;;; that the compiler knows to be a constant.)
222 (defstruct (constant-type
223             (:include ctype
224                       (class-info (type-class-or-lose 'constant)))
225             (:copier nil))
226   ;; The type which the argument must be a constant instance of for this type
227   ;; specifier to win.
228   (type (missing-arg) :type ctype))
229
230 ;;; The NAMED-TYPE is used to represent *, T and NIL. These types must
231 ;;; be super- or sub-types of all types, not just classes and * and
232 ;;; NIL aren't classes anyway, so it wouldn't make much sense to make
233 ;;; them built-in classes.
234 (defstruct (named-type (:include ctype
235                                  (class-info (type-class-or-lose 'named)))
236                        (:copier nil))
237   (name nil :type symbol))
238
239 ;;; a list of all the float "formats" (i.e. internal representations;
240 ;;; nothing to do with #'FORMAT), in order of decreasing precision
241 (eval-when (:compile-toplevel :load-toplevel :execute)
242   (defparameter *float-formats*
243     '(long-float double-float single-float short-float)))
244
245 ;;; The type of a float format.
246 (deftype float-format () `(member ,@*float-formats*))
247
248 ;;; A NUMERIC-TYPE represents any numeric type, including things
249 ;;; such as FIXNUM.
250 (defstruct (numeric-type (:include ctype
251                                    (class-info (type-class-or-lose 'number)))
252                          (:constructor %make-numeric-type)
253                          (:copier nil))
254   ;; the kind of numeric type we have, or NIL if not specified (just
255   ;; NUMBER or COMPLEX)
256   ;;
257   ;; KLUDGE: A slot named CLASS for a non-CLASS value is bad.
258   ;; Especially when a CLASS value *is* stored in another slot (called
259   ;; CLASS-INFO:-). Perhaps this should be called CLASS-NAME? Also
260   ;; weird that comment above says "Numeric-Type is used to represent
261   ;; all numeric types" but this slot doesn't allow COMPLEX as an
262   ;; option.. how does this fall into "not specified" NIL case above?
263   ;; Perhaps someday we can switch to CLOS and make NUMERIC-TYPE
264   ;; be an abstract base class and INTEGER-TYPE, RATIONAL-TYPE, and
265   ;; whatnot be concrete subclasses..
266   (class nil :type (member integer rational float nil) :read-only t)
267   ;; "format" for a float type (i.e. type specifier for a CPU
268   ;; representation of floating point, e.g. 'SINGLE-FLOAT -- nothing
269   ;; to do with #'FORMAT), or NIL if not specified or not a float.
270   ;; Formats which don't exist in a given implementation don't appear
271   ;; here.
272   (format nil :type (or float-format null) :read-only t)
273   ;; Is this a complex numeric type?  Null if unknown (only in NUMBER).
274   ;;
275   ;; FIXME: I'm bewildered by FOO-P names for things not intended to
276   ;; interpreted as truth values. Perhaps rename this COMPLEXNESS?
277   (complexp :real :type (member :real :complex nil) :read-only t)
278   ;; The upper and lower bounds on the value, or NIL if there is no
279   ;; bound. If a list of a number, the bound is exclusive. Integer
280   ;; types never have exclusive bounds, i.e. they may have them on
281   ;; input, but they're canonicalized to inclusive bounds before we
282   ;; store them here.
283   (low nil :type (or number cons null) :read-only t)
284   (high nil :type (or number cons null) :read-only t))
285
286 ;;; Impose canonicalization rules for NUMERIC-TYPE. Note that in some
287 ;;; cases, despite the name, we return *EMPTY-TYPE* instead of a
288 ;;; NUMERIC-TYPE.
289 (defun make-numeric-type (&key class format (complexp :real) low high
290                                enumerable)
291   ;; if interval is empty
292   (if (and low
293            high
294            (if (or (consp low) (consp high)) ; if either bound is exclusive
295                (>= (type-bound-number low) (type-bound-number high))
296                (> low high)))
297       *empty-type*
298       (multiple-value-bind (canonical-low canonical-high)
299           (case class
300             (integer
301              ;; INTEGER types always have their LOW and HIGH bounds
302              ;; represented as inclusive, not exclusive values.
303              (values (if (consp low)
304                          (1+ (type-bound-number low))
305                          low)
306                      (if (consp high)
307                          (1- (type-bound-number high))
308                          high)))
309             (t 
310              ;; no canonicalization necessary
311              (values low high)))
312         (when (and (eq class 'rational)
313                    (integerp canonical-low)
314                    (integerp canonical-high)
315                    (= canonical-low canonical-high))
316           (setf class 'integer))
317         (%make-numeric-type :class class
318                             :format format
319                             :complexp complexp
320                             :low canonical-low
321                             :high canonical-high
322                             :enumerable enumerable))))
323
324 (defun modified-numeric-type (base
325                               &key
326                               (class      (numeric-type-class      base))
327                               (format     (numeric-type-format     base))
328                               (complexp   (numeric-type-complexp   base))
329                               (low        (numeric-type-low        base))
330                               (high       (numeric-type-high       base))
331                               (enumerable (numeric-type-enumerable base)))
332   (make-numeric-type :class class
333                      :format format
334                      :complexp complexp
335                      :low low
336                      :high high
337                      :enumerable enumerable))
338
339 ;;; An ARRAY-TYPE is used to represent any array type, including
340 ;;; things such as SIMPLE-STRING.
341 (defstruct (array-type (:include ctype
342                                  (class-info (type-class-or-lose 'array)))
343                        (:constructor %make-array-type)
344                        (:copier nil))
345   ;; the dimensions of the array, or * if unspecified. If a dimension
346   ;; is unspecified, it is *.
347   (dimensions '* :type (or list (member *)))
348   ;; Is this not a simple array type? (:MAYBE means that we don't know.)
349   (complexp :maybe :type (member t nil :maybe))
350   ;; the element type as originally specified
351   (element-type (missing-arg) :type ctype)
352   ;; the element type as it is specialized in this implementation
353   (specialized-element-type *wild-type* :type ctype))
354 (define-cached-synonym make-array-type)
355
356 ;;; A MEMBER-TYPE represent a use of the MEMBER type specifier. We
357 ;;; bother with this at this level because MEMBER types are fairly
358 ;;; important and union and intersection are well defined.
359 (defstruct (member-type (:include ctype
360                                   (class-info (type-class-or-lose 'member))
361                                   (enumerable t))
362                         (:copier nil)
363                         (:constructor %make-member-type (members))
364                         #-sb-xc-host (:pure nil))
365   ;; the things in the set, with no duplications
366   (members nil :type list))
367 (defun make-member-type (&key members)
368   (declare (type list members))
369   ;; make sure that we've removed duplicates
370   (aver (= (length members) (length (remove-duplicates members))))
371   ;; if we have a pair of zeros (e.g. 0.0d0 and -0.0d0), then we can
372   ;; canonicalize to (DOUBLE-FLOAT 0.0d0 0.0d0), because numeric
373   ;; ranges are compared by arithmetic operators (while MEMBERship is
374   ;; compared by EQL).  -- CSR, 2003-04-23
375   (let ((singlep (subsetp `(,(load-time-value (make-unportable-float :single-float-negative-zero)) 0.0f0) members))
376         (doublep (subsetp `(,(load-time-value (make-unportable-float :double-float-negative-zero)) 0.0d0) members))
377         #!+long-float
378         (longp (subsetp `(,(load-time-value (make-unportable-float :long-float-negative-zero)) 0.0l0) members)))
379     (if (or singlep doublep #!+long-float longp)
380         (let (union-types)
381           (when singlep
382             (push (ctype-of 0.0f0) union-types)
383             (setf members (set-difference members `(,(load-time-value (make-unportable-float :single-float-negative-zero)) 0.0f0))))
384           (when doublep
385             (push (ctype-of 0.0d0) union-types)
386             (setf members (set-difference members `(,(load-time-value (make-unportable-float :double-float-negative-zero)) 0.0d0))))
387           #!+long-float
388           (when longp
389             (push (ctype-of 0.0l0) union-types)
390             (setf members (set-difference members `(,(load-time-value (make-unportable-float :long-float-negative-zero)) 0.0l0))))
391           (aver (not (null union-types)))
392           (make-union-type t
393                            (if (null members)
394                                union-types
395                                (cons (%make-member-type members)
396                                      union-types))))
397         (%make-member-type members))))
398
399 ;;; A COMPOUND-TYPE is a type defined out of a set of types, the
400 ;;; common parent of UNION-TYPE and INTERSECTION-TYPE.
401 (defstruct (compound-type (:include ctype
402                                     (might-contain-other-types-p t))
403                           (:constructor nil)
404                           (:copier nil))
405   (types nil :type list :read-only t))
406
407 ;;; A UNION-TYPE represents a use of the OR type specifier which we
408 ;;; couldn't canonicalize to something simpler. Canonical form:
409 ;;;   1. All possible pairwise simplifications (using the UNION2 type
410 ;;;      methods) have been performed. Thus e.g. there is never more
411 ;;;      than one MEMBER-TYPE component. FIXME: As of sbcl-0.6.11.13,
412 ;;;      this hadn't been fully implemented yet.
413 ;;;   2. There are never any UNION-TYPE components.
414 (defstruct (union-type (:include compound-type
415                                  (class-info (type-class-or-lose 'union)))
416                        (:constructor %make-union-type (enumerable types))
417                        (:copier nil)))
418 (define-cached-synonym make-union-type)
419
420 ;;; An INTERSECTION-TYPE represents a use of the AND type specifier
421 ;;; which we couldn't canonicalize to something simpler. Canonical form:
422 ;;;   1. All possible pairwise simplifications (using the INTERSECTION2
423 ;;;      type methods) have been performed. Thus e.g. there is never more
424 ;;;      than one MEMBER-TYPE component.
425 ;;;   2. There are never any INTERSECTION-TYPE components: we've
426 ;;;      flattened everything into a single INTERSECTION-TYPE object.
427 ;;;   3. There are never any UNION-TYPE components. Either we should
428 ;;;      use the distributive rule to rearrange things so that
429 ;;;      unions contain intersections and not vice versa, or we
430 ;;;      should just punt to using a HAIRY-TYPE.
431 (defstruct (intersection-type (:include compound-type
432                                         (class-info (type-class-or-lose
433                                                      'intersection)))
434                               (:constructor %make-intersection-type
435                                             (enumerable types))
436                               (:copier nil)))
437
438 ;;; Return TYPE converted to canonical form for a situation where the
439 ;;; "type" '* (which SBCL still represents as a type even though ANSI
440 ;;; CL defines it as a related but different kind of placeholder) is
441 ;;; equivalent to type T.
442 (defun type-*-to-t (type)
443   (if (type= type *wild-type*)
444       *universal-type*
445       type))
446
447 ;;; A CONS-TYPE is used to represent a CONS type.
448 (defstruct (cons-type (:include ctype (class-info (type-class-or-lose 'cons)))
449                       (:constructor
450                        %make-cons-type (car-type
451                                         cdr-type))
452                       (:copier nil))
453   ;; the CAR and CDR element types (to support ANSI (CONS FOO BAR) types)
454   ;;
455   ;; FIXME: Most or all other type structure slots could also be :READ-ONLY.
456   (car-type (missing-arg) :type ctype :read-only t)
457   (cdr-type (missing-arg) :type ctype :read-only t))
458 (defun make-cons-type (car-type cdr-type)
459   (aver (not (or (eq car-type *wild-type*)
460                  (eq cdr-type *wild-type*))))
461   (if (or (eq car-type *empty-type*)
462           (eq cdr-type *empty-type*))
463       *empty-type*
464       (%make-cons-type car-type cdr-type)))
465 \f
466 ;;;; type utilities
467
468 ;;; Return the type structure corresponding to a type specifier. We
469 ;;; pick off structure types as a special case.
470 ;;;
471 ;;; Note: VALUES-SPECIFIER-TYPE-CACHE-CLEAR must be called whenever a
472 ;;; type is defined (or redefined).
473 (defun-cached (values-specifier-type
474                :hash-function (lambda (x)
475                                 (logand (sxhash x) #x3FF))
476                :hash-bits 10
477                :init-wrapper !cold-init-forms)
478               ((orig equal-but-no-car-recursion))
479   (let ((u (uncross orig)))
480     (or (info :type :builtin u)
481         (let ((spec (type-expand u)))
482           (cond
483            ((and (not (eq spec u))
484                  (info :type :builtin spec)))
485            ((eq (info :type :kind spec) :instance)
486             (find-classoid spec))
487            ((typep spec 'classoid)
488             ;; There doesn't seem to be any way to translate
489             ;; (TYPEP SPEC 'BUILT-IN-CLASS) into something which can be
490             ;; executed on the host Common Lisp at cross-compilation time.
491             #+sb-xc-host (error
492                           "stub: (TYPEP SPEC 'BUILT-IN-CLASS) on xc host")
493             (if (typep spec 'built-in-classoid)
494                 (or (built-in-classoid-translation spec) spec)
495                 spec))
496            (t
497             (when (and (atom spec)
498                        (member spec '(and or not member eql satisfies values)))
499               (error "The symbol ~S is not valid as a type specifier." spec))
500             (let* ((lspec (if (atom spec) (list spec) spec))
501                    (fun (info :type :translator (car lspec))))
502               (cond (fun
503                      (funcall fun lspec))
504                     ((or (and (consp spec) (symbolp (car spec)))
505                          (symbolp spec))
506                      (when (and *type-system-initialized*
507                                 (not (eq (info :type :kind spec)
508                                          :forthcoming-defclass-type)))
509                        (signal 'parse-unknown-type :specifier spec))
510                      ;; (The RETURN-FROM here inhibits caching.)
511                      (return-from values-specifier-type
512                        (make-unknown-type :specifier spec)))
513                     (t
514                      (error "bad thing to be a type specifier: ~S"
515                             spec))))))))))
516
517 ;;; This is like VALUES-SPECIFIER-TYPE, except that we guarantee to
518 ;;; never return a VALUES type.
519 (defun specifier-type (x)
520   (let ((res (values-specifier-type x)))
521     (when (or (values-type-p res)
522               ;; bootstrap magic :-(
523               (and (named-type-p res)
524                    (eq (named-type-name res) '*)))
525       (error "VALUES type illegal in this context:~%  ~S" x))
526     res))
527
528 (defun single-value-specifier-type (x)
529   (if (eq x '*)
530       *universal-type*
531       (specifier-type x)))
532
533 ;;; Similar to MACROEXPAND, but expands DEFTYPEs. We don't bother
534 ;;; returning a second value.
535 (defun type-expand (form)
536   (let ((def (cond ((symbolp form)
537                     (info :type :expander form))
538                    ((and (consp form) (symbolp (car form)))
539                     (info :type :expander (car form)))
540                    (t nil))))
541     (if def
542         (type-expand (funcall def (if (consp form) form (list form))))
543         form)))
544
545 ;;; Note that the type NAME has been (re)defined, updating the
546 ;;; undefined warnings and VALUES-SPECIFIER-TYPE cache.
547 (defun %note-type-defined (name)
548   (declare (symbol name))
549   (note-name-defined name :type)
550   (when (boundp 'sb!kernel::*values-specifier-type-cache-vector*)
551     (values-specifier-type-cache-clear))
552   (values))
553
554 \f
555 (!defun-from-collected-cold-init-forms !early-type-cold-init)