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