Make type caches perform better.
[sbcl.git] / src / code / early-type.lisp
blob2797eac27720c94adfce03f5ed2d499617c58201
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.
10 (in-package "SB!KERNEL")
12 (!begin-collecting-cold-init-forms)
14 ;;;; representations of types
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 (:constructor %make-hairy-type (specifier))
23 (:copier nil)
24 #!+cmu (:pure nil))
25 ;; the Common Lisp type-specifier of the type we represent
26 (specifier nil :type t :read-only t))
28 ;; ENUMERABLE-P is T because a hairy type could be equivalent to a MEMBER type.
29 ;; e.g. any SATISFIES with a predicate returning T over a finite domain.
30 ;; But in practice there's nothing that can be done with this information,
31 ;; because we don't call random predicates when performing operations on types
32 ;; as objects, only when checking for inclusion of something in the type.
33 (!define-type-class hairy :enumerable t :might-contain-other-types t)
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)))
41 (defun maybe-reparse-specifier (type)
42 (when (unknown-type-p type)
43 (let* ((spec (unknown-type-specifier type))
44 (name (if (consp spec)
45 (car spec)
46 spec)))
47 (when (info :type :kind name)
48 (let ((new-type (specifier-type spec)))
49 (unless (unknown-type-p new-type)
50 new-type))))))
52 ;;; Evil macro.
53 (defmacro maybe-reparse-specifier! (type)
54 (assert (symbolp type))
55 (with-unique-names (new-type)
56 `(let ((,new-type (maybe-reparse-specifier ,type)))
57 (when ,new-type
58 (setf ,type ,new-type)
59 t))))
61 (defstruct (negation-type (:include ctype
62 (class-info (type-class-or-lose 'negation)))
63 (:copier nil)
64 #!+cmu (:pure nil))
65 (type (missing-arg) :type ctype :read-only t))
67 ;; Former comment was:
68 ;; FIXME: is this right? It's what they had before, anyway
69 ;; But I think the reason it's right is that "enumerable :t" is equivalent
70 ;; to "maybe" which is actually the conservative assumption, same as HAIRY.
71 (!define-type-class negation :enumerable t :might-contain-other-types t)
73 ;;; ARGS-TYPE objects are used both to represent VALUES types and
74 ;;; to represent FUNCTION types.
75 (defstruct (args-type (:include ctype)
76 (:constructor nil)
77 (:copier nil))
78 ;; Lists of the type for each required and optional argument.
79 (required nil :type list :read-only t)
80 (optional nil :type list :read-only t)
81 ;; The type for the rest arg. NIL if there is no &REST arg.
82 (rest nil :type (or ctype null) :read-only t)
83 ;; true if &KEY arguments are specified
84 (keyp nil :type boolean :read-only t)
85 ;; list of KEY-INFO structures describing the &KEY arguments
86 (keywords nil :type list :read-only t)
87 ;; true if other &KEY arguments are allowed
88 (allowp nil :type boolean :read-only t))
90 (defun canonicalize-args-type-args (required optional rest &optional keyp)
91 (when (eq rest *empty-type*)
92 ;; or vice-versa?
93 (setq rest nil))
94 (loop with last-not-rest = nil
95 for i from 0
96 for opt in optional
97 do (cond ((eq opt *empty-type*)
98 (return (values required (subseq optional i) rest)))
99 ((and (not keyp) (neq opt rest))
100 (setq last-not-rest i)))
101 finally (return (values required
102 (cond (keyp
103 optional)
104 (last-not-rest
105 (subseq optional 0 (1+ last-not-rest))))
106 rest))))
108 (defun parse-args-types (lambda-list-like-thing)
109 (multiple-value-bind
110 (required optional restp rest keyp keys allowp auxp aux
111 morep more-context more-count llk-p)
112 (parse-lambda-list-like-thing lambda-list-like-thing :silent t)
113 (declare (ignore aux morep more-context more-count))
114 (when auxp
115 (error "&AUX in a FUNCTION or VALUES type: ~S." lambda-list-like-thing))
116 (let ((required (mapcar #'single-value-specifier-type required))
117 (optional (mapcar #'single-value-specifier-type optional))
118 (rest (when restp (single-value-specifier-type rest)))
119 (keywords
120 (collect ((key-info))
121 (dolist (key keys)
122 (unless (proper-list-of-length-p key 2)
123 (error "Keyword type description is not a two-list: ~S." key))
124 (let ((kwd (first key)))
125 (when (find kwd (key-info) :key #'key-info-name)
126 (error "~@<repeated keyword ~S in lambda list: ~2I~_~S~:>"
127 kwd lambda-list-like-thing))
128 (key-info
129 (make-key-info
130 :name kwd
131 :type (single-value-specifier-type (second key))))))
132 (key-info))))
133 (multiple-value-bind (required optional rest)
134 (canonicalize-args-type-args required optional rest keyp)
135 (values required optional rest keyp keywords allowp llk-p)))))
137 (defstruct (values-type
138 (:include args-type
139 (class-info (type-class-or-lose 'values)))
140 (:constructor %make-values-type)
141 (:predicate %values-type-p)
142 (:copier nil)))
144 (declaim (inline values-type-p))
145 (defun values-type-p (x)
146 (or (eq x *wild-type*)
147 (%values-type-p x)))
149 (defun-cached (make-values-type-cached
150 :hash-bits 8
151 :hash-function
152 (lambda (req opt rest allowp)
153 (logxor (type-list-cache-hash req)
154 (type-list-cache-hash opt)
155 (if rest
156 (type-hash-value rest)
158 ;; Results (logand #xFF (sxhash t/nil))
159 ;; hardcoded to avoid relying on the xc host.
160 ;; [but (logand (sxhash nil) #xff) => 2
161 ;; for me, so the code and comment disagree,
162 ;; but not in a way that matters.]
163 (if allowp
165 11))))
166 ((required equal-but-no-car-recursion)
167 (optional equal-but-no-car-recursion)
168 (rest eq)
169 (allowp eq))
170 (%make-values-type :required required
171 :optional optional
172 :rest rest
173 :allowp allowp))
175 (defun make-values-type (&key required optional rest allowp)
176 (multiple-value-bind (required optional rest)
177 (canonicalize-args-type-args required optional rest)
178 (cond ((and (null required)
179 (null optional)
180 (eq rest *universal-type*))
181 *wild-type*)
182 ((memq *empty-type* required)
183 *empty-type*)
184 (t (make-values-type-cached required optional
185 rest allowp)))))
187 (!define-type-class values :enumerable nil
188 :might-contain-other-types nil)
190 ;;; (SPECIFIER-TYPE 'FUNCTION) and its subtypes
191 (defstruct (fun-type (:include args-type
192 (class-info (type-class-or-lose 'function)))
193 (:constructor
194 make-fun-type (&key required optional rest
195 keyp keywords allowp
196 wild-args
197 returns
198 &aux (rest (if (eq rest *empty-type*)
200 rest)))))
201 ;; true if the arguments are unrestrictive, i.e. *
202 (wild-args nil :type boolean :read-only t)
203 ;; type describing the return values. This is a values type
204 ;; when multiple values were specified for the return.
205 (returns (missing-arg) :type ctype :read-only t))
207 ;;; The CONSTANT-TYPE structure represents a use of the CONSTANT-ARG
208 ;;; "type specifier", which is only meaningful in function argument
209 ;;; type specifiers used within the compiler. (It represents something
210 ;;; that the compiler knows to be a constant.)
211 (defstruct (constant-type
212 (:include ctype
213 (class-info (type-class-or-lose 'constant)))
214 (:copier nil))
215 ;; The type which the argument must be a constant instance of for this type
216 ;; specifier to win.
217 (type (missing-arg) :type ctype :read-only t))
219 ;;; The NAMED-TYPE is used to represent *, T and NIL, the standard
220 ;;; special cases, as well as other special cases needed to
221 ;;; interpolate between regions of the type hierarchy, such as
222 ;;; INSTANCE (which corresponds to all those classes with slots which
223 ;;; are not funcallable), FUNCALLABLE-INSTANCE (those classes with
224 ;;; slots which are funcallable) and EXTENDED-SEQUUENCE (non-LIST
225 ;;; non-VECTOR classes which are also sequences). These special cases
226 ;;; are the ones that aren't really discussed by Baker in his
227 ;;; "Decision Procedure for SUBTYPEP" paper.
228 (defstruct (named-type (:include ctype
229 (class-info (type-class-or-lose 'named)))
230 (:copier nil))
231 (name nil :type symbol :read-only t))
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)))
239 ;;; The type of a float format.
240 (deftype float-format () `(member ,@*float-formats*))
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 ;; Formerly defined in every CTYPE, but now just in the ones
249 ;; for which enumerability is variable.
250 (enumerable nil :read-only t)
251 ;; the kind of numeric type we have, or NIL if not specified (just
252 ;; NUMBER or COMPLEX)
254 ;; KLUDGE: A slot named CLASS for a non-CLASS value is bad.
255 ;; Especially when a CLASS value *is* stored in another slot (called
256 ;; CLASS-INFO:-). Perhaps this should be called CLASS-NAME? Also
257 ;; weird that comment above says "Numeric-Type is used to represent
258 ;; all numeric types" but this slot doesn't allow COMPLEX as an
259 ;; option.. how does this fall into "not specified" NIL case above?
260 ;; Perhaps someday we can switch to CLOS and make NUMERIC-TYPE
261 ;; be an abstract base class and INTEGER-TYPE, RATIONAL-TYPE, and
262 ;; whatnot be concrete subclasses..
263 (class nil :type (member integer rational float nil) :read-only t)
264 ;; "format" for a float type (i.e. type specifier for a CPU
265 ;; representation of floating point, e.g. 'SINGLE-FLOAT -- nothing
266 ;; to do with #'FORMAT), or NIL if not specified or not a float.
267 ;; Formats which don't exist in a given implementation don't appear
268 ;; here.
269 (format nil :type (or float-format null) :read-only t)
270 ;; Is this a complex numeric type? Null if unknown (only in NUMBER).
272 ;; FIXME: I'm bewildered by FOO-P names for things not intended to
273 ;; interpreted as truth values. Perhaps rename this COMPLEXNESS?
274 (complexp :real :type (member :real :complex nil) :read-only t)
275 ;; The upper and lower bounds on the value, or NIL if there is no
276 ;; bound. If a list of a number, the bound is exclusive. Integer
277 ;; types never have exclusive bounds, i.e. they may have them on
278 ;; input, but they're canonicalized to inclusive bounds before we
279 ;; store them here.
280 (low nil :type (or number cons null) :read-only t)
281 (high nil :type (or number cons null) :read-only t))
283 ;;; Impose canonicalization rules for NUMERIC-TYPE. Note that in some
284 ;;; cases, despite the name, we return *EMPTY-TYPE* instead of a
285 ;;; NUMERIC-TYPE.
286 (defun make-numeric-type (&key class format (complexp :real) low high
287 enumerable)
288 ;; if interval is empty
289 (if (and low
290 high
291 (if (or (consp low) (consp high)) ; if either bound is exclusive
292 (>= (type-bound-number low) (type-bound-number high))
293 (> low high)))
294 *empty-type*
295 (multiple-value-bind (canonical-low canonical-high)
296 (case class
297 (integer
298 ;; INTEGER types always have their LOW and HIGH bounds
299 ;; represented as inclusive, not exclusive values.
300 (values (if (consp low)
301 (1+ (type-bound-number low))
302 low)
303 (if (consp high)
304 (1- (type-bound-number high))
305 high)))
307 ;; no canonicalization necessary
308 (values low high)))
309 (when (and (eq class 'rational)
310 (integerp canonical-low)
311 (integerp canonical-high)
312 (= canonical-low canonical-high))
313 (setf class 'integer))
314 (%make-numeric-type :class class
315 :format format
316 :complexp complexp
317 :low canonical-low
318 :high canonical-high
319 :enumerable enumerable))))
321 (defun modified-numeric-type (base
322 &key
323 (class (numeric-type-class base))
324 (format (numeric-type-format base))
325 (complexp (numeric-type-complexp base))
326 (low (numeric-type-low base))
327 (high (numeric-type-high base))
328 (enumerable (type-enumerable base)))
329 (make-numeric-type :class class
330 :format format
331 :complexp complexp
332 :low low
333 :high high
334 :enumerable enumerable))
336 (defstruct (character-set-type
337 (:include ctype
338 (class-info (type-class-or-lose 'character-set)))
339 (:constructor %make-character-set-type)
340 (:copier nil))
341 (pairs (missing-arg) :type list :read-only t))
342 (defun make-character-set-type (&key pairs)
343 ; (aver (equal (mapcar #'car pairs)
344 ; (sort (mapcar #'car pairs) #'<)))
345 ;; aver that the cars of the list elements are sorted into increasing order
346 (aver (or (null pairs)
347 (do ((p pairs (cdr p)))
348 ((null (cdr p)) t)
349 (when (> (caar p) (caadr p)) (return nil)))))
350 (let ((pairs (let (result)
351 (do ((pairs pairs (cdr pairs)))
352 ((null pairs) (nreverse result))
353 (destructuring-bind (low . high) (car pairs)
354 (loop for (low1 . high1) in (cdr pairs)
355 if (<= low1 (1+ high))
356 do (progn (setf high (max high high1))
357 (setf pairs (cdr pairs)))
358 else do (return nil))
359 (cond
360 ((>= low sb!xc:char-code-limit))
361 ((< high 0))
362 (t (push (cons (max 0 low)
363 (min high (1- sb!xc:char-code-limit)))
364 result))))))))
365 (if (null pairs)
366 *empty-type*
367 (%make-character-set-type :pairs pairs))))
369 ;;; An ARRAY-TYPE is used to represent any array type, including
370 ;;; things such as SIMPLE-BASE-STRING.
371 (defstruct (array-type (:include ctype
372 (class-info (type-class-or-lose 'array)))
373 (:constructor make-array-type
374 (dimensions &key complexp element-type
375 specialized-element-type))
376 (:copier nil))
377 ;; the dimensions of the array, or * if unspecified. If a dimension
378 ;; is unspecified, it is *.
379 (dimensions '* :type (or list (member *)) :read-only t)
380 ;; Is this not a simple array type? (:MAYBE means that we don't know.)
381 (complexp :maybe :type (member t nil :maybe) :read-only t)
382 ;; the element type as originally specified
383 (element-type (missing-arg) :type ctype :read-only t)
384 ;; the element type as it is specialized in this implementation
385 (specialized-element-type *wild-type* :type ctype :read-only t))
387 ;;; A MEMBER-TYPE represent a use of the MEMBER type specifier. We
388 ;;; bother with this at this level because MEMBER types are fairly
389 ;;; important and union and intersection are well defined.
390 (defstruct (member-type (:include ctype
391 (class-info (type-class-or-lose 'member)))
392 (:copier nil)
393 (:constructor %make-member-type (xset fp-zeroes))
394 #-sb-xc-host (:pure nil))
395 (xset (missing-arg) :type xset :read-only t)
396 (fp-zeroes (missing-arg) :type list :read-only t))
397 (defun make-member-type (&key xset fp-zeroes members)
398 (unless xset
399 (aver (not fp-zeroes))
400 (setf xset (alloc-xset))
401 (dolist (elt members)
402 (if (fp-zero-p elt)
403 (pushnew elt fp-zeroes)
404 (add-to-xset elt xset))))
405 ;; if we have a pair of zeros (e.g. 0.0d0 and -0.0d0), then we can
406 ;; canonicalize to (DOUBLE-FLOAT 0.0d0 0.0d0), because numeric
407 ;; ranges are compared by arithmetic operators (while MEMBERship is
408 ;; compared by EQL). -- CSR, 2003-04-23
409 (let ((presence 0)
410 (unpaired nil)
411 (float-types nil))
412 (when fp-zeroes ; avoid doing two passes of nothing
413 (dotimes (pass 2)
414 (dolist (z fp-zeroes)
415 (let ((sign (if (minusp (nth-value 2 (integer-decode-float z))) 1 0))
416 (pair-idx
417 (etypecase z
418 (single-float 0)
419 (double-float 2
420 #!+long-float (long-float 4)))))
421 (if (= pass 0)
422 (setf (ldb (byte 1 (+ pair-idx sign)) presence) 1)
423 (if (= (ldb (byte 2 pair-idx) presence) #b11)
424 (when (= sign 0)
425 (push (ctype-of z) float-types))
426 (push z unpaired)))))))
427 ;; The actual member-type contains the XSET (with no FP zeroes),
428 ;; and a list of unpaired zeroes.
429 (let ((member-type
430 (cond ((and (not unpaired) (equal (xset-data xset) '(nil)))
431 *null-type*)
432 ((and (not unpaired)
433 ;; Semantically this is fine - XSETs
434 ;; are not order-preserving except by accident
435 ;; (when not represented as a hash-table).
436 (or (equal (xset-data xset) '(t nil))
437 (equal (xset-data xset) '(nil t))))
438 *boolean-type*)
439 ((or unpaired (not (xset-empty-p xset)))
440 (%make-member-type xset unpaired)))))
441 (if float-types
442 (make-union-type t (if member-type
443 (cons member-type float-types)
444 float-types))
445 (or member-type *empty-type*)))))
447 (defun member-type-size (type)
448 (+ (length (member-type-fp-zeroes type))
449 (xset-count (member-type-xset type))))
451 (defun member-type-member-p (x type)
452 (if (fp-zero-p x)
453 (and (member x (member-type-fp-zeroes type)) t)
454 (xset-member-p x (member-type-xset type))))
456 (defun mapcar-member-type-members (function type)
457 (declare (function function))
458 (collect ((results))
459 (map-xset (lambda (x)
460 (results (funcall function x)))
461 (member-type-xset type))
462 (dolist (zero (member-type-fp-zeroes type))
463 (results (funcall function zero)))
464 (results)))
466 (defun mapc-member-type-members (function type)
467 (declare (function function))
468 (map-xset function (member-type-xset type))
469 (dolist (zero (member-type-fp-zeroes type))
470 (funcall function zero)))
472 (defun member-type-members (type)
473 (append (member-type-fp-zeroes type)
474 (xset-members (member-type-xset type))))
476 ;;; A COMPOUND-TYPE is a type defined out of a set of types, the
477 ;;; common parent of UNION-TYPE and INTERSECTION-TYPE.
478 (defstruct (compound-type (:include ctype)
479 (:constructor nil)
480 (:copier nil))
481 ;; Formerly defined in every CTYPE, but now just in the ones
482 ;; for which enumerability is variable.
483 (enumerable nil :read-only t)
484 (types nil :type list :read-only t))
486 ;;; A UNION-TYPE represents a use of the OR type specifier which we
487 ;;; couldn't canonicalize to something simpler. Canonical form:
488 ;;; 1. All possible pairwise simplifications (using the UNION2 type
489 ;;; methods) have been performed. Thus e.g. there is never more
490 ;;; than one MEMBER-TYPE component. FIXME: As of sbcl-0.6.11.13,
491 ;;; this hadn't been fully implemented yet.
492 ;;; 2. There are never any UNION-TYPE components.
493 (defstruct (union-type (:include compound-type
494 (class-info (type-class-or-lose 'union)))
495 (:constructor make-union-type (enumerable types))
496 (:copier nil)))
498 ;;; An INTERSECTION-TYPE represents a use of the AND type specifier
499 ;;; which we couldn't canonicalize to something simpler. Canonical form:
500 ;;; 1. All possible pairwise simplifications (using the INTERSECTION2
501 ;;; type methods) have been performed. Thus e.g. there is never more
502 ;;; than one MEMBER-TYPE component.
503 ;;; 2. There are never any INTERSECTION-TYPE components: we've
504 ;;; flattened everything into a single INTERSECTION-TYPE object.
505 ;;; 3. There are never any UNION-TYPE components. Either we should
506 ;;; use the distributive rule to rearrange things so that
507 ;;; unions contain intersections and not vice versa, or we
508 ;;; should just punt to using a HAIRY-TYPE.
509 (defstruct (intersection-type (:include compound-type
510 (class-info (type-class-or-lose
511 'intersection)))
512 (:constructor %make-intersection-type
513 (enumerable types))
514 (:copier nil)))
516 ;;; Return TYPE converted to canonical form for a situation where the
517 ;;; "type" '* (which SBCL still represents as a type even though ANSI
518 ;;; CL defines it as a related but different kind of placeholder) is
519 ;;; equivalent to type T.
520 (defun type-*-to-t (type)
521 (if (type= type *wild-type*)
522 *universal-type*
523 type))
525 ;;; A CONS-TYPE is used to represent a CONS type.
526 (defstruct (cons-type (:include ctype (class-info (type-class-or-lose 'cons)))
527 (:constructor
528 %make-cons-type (car-type
529 cdr-type))
530 (:copier nil))
531 ;; the CAR and CDR element types (to support ANSI (CONS FOO BAR) types)
532 (car-type (missing-arg) :type ctype :read-only t)
533 (cdr-type (missing-arg) :type ctype :read-only t))
534 (defun make-cons-type (car-type cdr-type)
535 (aver (not (or (eq car-type *wild-type*)
536 (eq cdr-type *wild-type*))))
537 (cond ((or (eq car-type *empty-type*)
538 (eq cdr-type *empty-type*))
539 *empty-type*)
540 ;; It's not a requirement that (CONS T T) be interned,
541 ;; but it improves the hit rate in the function caches.
542 ((and (type= car-type *universal-type*)
543 (type= cdr-type *universal-type*))
544 *cons-t-t-type*)
546 (%make-cons-type car-type cdr-type))))
548 (defun cons-type-length-info (type)
549 (declare (type cons-type type))
550 (do ((min 1 (1+ min))
551 (cdr (cons-type-cdr-type type) (cons-type-cdr-type cdr)))
552 ((not (cons-type-p cdr))
553 (cond
554 ((csubtypep cdr (specifier-type 'null))
555 (values min t))
556 ((csubtypep *universal-type* cdr)
557 (values min nil))
558 ((type/= (type-intersection (specifier-type 'cons) cdr) *empty-type*)
559 (values min nil))
560 ((type/= (type-intersection (specifier-type 'null) cdr) *empty-type*)
561 (values min t))
562 (t (values min :maybe))))
563 ()))
565 ;;; A SIMD-PACK-TYPE is used to represent a SIMD-PACK type.
566 #!+sb-simd-pack
567 (defstruct (simd-pack-type
568 (:include ctype (class-info (type-class-or-lose 'simd-pack)))
569 (:constructor %make-simd-pack-type (element-type))
570 (:copier nil))
571 (element-type (missing-arg)
572 :type (cons #||(member #.*simd-pack-element-types*) ||#)
573 :read-only t))
575 #!+sb-simd-pack
576 (defun make-simd-pack-type (element-type)
577 (aver (neq element-type *wild-type*))
578 (if (eq element-type *empty-type*)
579 *empty-type*
580 (%make-simd-pack-type
581 (dolist (pack-type *simd-pack-element-types*
582 (error "~S element type must be a subtype of ~
583 ~{~S~#[~;, or ~:;, ~]~}."
584 'simd-pack *simd-pack-element-types*))
585 (when (csubtypep element-type (specifier-type pack-type))
586 (return (list pack-type)))))))
589 ;;;; type utilities
591 ;;; Return the type structure corresponding to a type specifier. We
592 ;;; pick off structure types as a special case.
594 ;;; Note: VALUES-SPECIFIER-TYPE-CACHE-CLEAR must be called whenever a
595 ;;; type is defined (or redefined).
596 ;;; This cache is sized extremely generously, which has payoff
597 ;;; elsewhere: it improves the TYPE= and CSUBTYPEP functions,
598 ;;; since EQ types are an immediate win.
600 ;;; KLUDGE: why isn't this a MACROLET? "lexical environment too
601 ;;; hairy"
602 (defmacro !values-specifier-type-body (arg)
603 `(let ((u (uncross ,arg)))
604 (or (info :type :builtin u)
605 (let ((spec (typexpand u)))
606 (cond
607 ((and (not (eq spec u))
608 (info :type :builtin spec)))
609 ((and (consp spec) (symbolp (car spec))
610 (info :type :builtin (car spec))
611 (let ((expander (info :type :expander (car spec))))
612 (and expander (values-specifier-type (funcall expander spec))))))
613 ((eq (info :type :kind spec) :instance)
614 (find-classoid spec))
615 ((typep spec 'classoid)
616 (if (typep spec 'built-in-classoid)
617 (or (built-in-classoid-translation spec) spec)
618 spec))
620 (when (and (atom spec)
621 (member spec '(and or not member eql satisfies values)))
622 (error "The symbol ~S is not valid as a type specifier." spec))
623 (let ((fun (info :type :translator (if (consp spec) (car spec) spec))))
624 (cond (fun
625 (funcall fun (if (atom spec) (list spec) spec)))
626 ((or (and (consp spec) (symbolp (car spec))
627 (not (info :type :builtin (car spec))))
628 (and (symbolp spec) (not (info :type :builtin spec))))
629 (when (and *type-system-initialized*
630 (not (eq (info :type :kind spec)
631 :forthcoming-defclass-type)))
632 (signal 'parse-unknown-type :specifier spec))
633 ;; (The RETURN-FROM here inhibits caching; this
634 ;; does not only make sense from a compiler
635 ;; diagnostics point of view but is also
636 ;; indispensable for proper workingness of
637 ;; VALID-TYPE-SPECIFIER-P.)
638 (return-from values-specifier-type
639 (make-unknown-type :specifier spec)))
641 (error "bad thing to be a type specifier: ~S"
642 spec))))))))))
643 #+sb-xc-host
644 (let ((table (make-hash-table :test 'equal)))
645 (defun values-specifier-type (specifier)
646 (multiple-value-bind (type yesp) (gethash specifier table)
647 (if yesp
648 type
649 (setf (gethash specifier table)
650 (!values-specifier-type-body specifier)))))
651 (defun values-specifier-type-cache-clear ()
652 (clrhash table)))
653 #-sb-xc-host
654 (defun-cached (values-specifier-type
655 :hash-function #'sxhash :hash-bits 10)
656 ((orig equal-but-no-car-recursion))
657 (!values-specifier-type-body orig))
659 ;;; This is like VALUES-SPECIFIER-TYPE, except that we guarantee to
660 ;;; never return a VALUES type.
661 (defun specifier-type (x)
662 (let ((res (values-specifier-type x)))
663 (when (or (values-type-p res)
664 ;; bootstrap magic :-(
665 (and (named-type-p res)
666 (eq (named-type-name res) '*)))
667 (error "VALUES type illegal in this context:~% ~S" x))
668 res))
670 (defun single-value-specifier-type (x)
671 (if (eq x '*)
672 *universal-type*
673 (specifier-type x)))
675 (defun typexpand-1 (type-specifier &optional env)
676 #!+sb-doc
677 "Takes and expands a type specifier once like MACROEXPAND-1.
678 Returns two values: the expansion, and a boolean that is true when
679 expansion happened."
680 (declare (type type-specifier type-specifier))
681 (declare (ignore env))
682 (multiple-value-bind (expander lspec)
683 (let ((spec type-specifier))
684 (cond ((and (symbolp spec) (info :type :builtin spec))
685 ;; We do not expand builtins even though it'd be
686 ;; possible to do so sometimes (e.g. STRING) for two
687 ;; reasons:
689 ;; a) From a user's point of view, CL types are opaque.
691 ;; b) so (EQUAL (TYPEXPAND 'STRING) (TYPEXPAND-ALL 'STRING))
692 (values nil nil))
693 ((symbolp spec)
694 (values (info :type :expander spec) spec))
695 ((and (consp spec) (symbolp (car spec)) (info :type :builtin (car spec)))
696 ;; see above
697 (values nil nil))
698 ((and (consp spec) (symbolp (car spec)))
699 (values (info :type :expander (car spec)) spec))
700 (t nil)))
701 (if expander
702 (values (funcall expander (if (symbolp lspec)
703 (list lspec)
704 lspec))
706 (values type-specifier nil))))
708 (defun typexpand (type-specifier &optional env)
709 #!+sb-doc
710 "Takes and expands a type specifier repeatedly like MACROEXPAND.
711 Returns two values: the expansion, and a boolean that is true when
712 expansion happened."
713 (declare (type type-specifier type-specifier))
714 (multiple-value-bind (expansion flag)
715 (typexpand-1 type-specifier env)
716 (if flag
717 (values (typexpand expansion env) t)
718 (values expansion flag))))
720 (defun typexpand-all (type-specifier &optional env)
721 #!+sb-doc
722 "Takes and expands a type specifier recursively like MACROEXPAND-ALL."
723 (declare (type type-specifier type-specifier))
724 (declare (ignore env))
725 ;; I first thought this would not be a good implementation because
726 ;; it signals an error on e.g. (CONS 1 2) until I realized that
727 ;; walking and calling TYPEXPAND would also result in errors, and
728 ;; it actually makes sense.
730 ;; There's still a small problem in that
731 ;; (TYPEXPAND-ALL '(CONS * FIXNUM)) => (CONS T FIXNUM)
732 ;; whereas walking+typexpand would result in (CONS * FIXNUM).
734 ;; Similiarly, (TYPEXPAND-ALL '(FUNCTION (&REST T) *)) => FUNCTION.
735 (type-specifier (values-specifier-type type-specifier)))
737 (defun defined-type-name-p (name &optional env)
738 #!+sb-doc
739 "Returns T if NAME is known to name a type specifier, otherwise NIL."
740 (declare (symbol name))
741 (declare (ignore env))
742 (and (info :type :kind name) t))
744 (defun valid-type-specifier-p (type-specifier &optional env)
745 #!+sb-doc
746 "Returns T if TYPE-SPECIFIER is a valid type specifier, otherwise NIL.
748 There may be different metrics on what constitutes a \"valid type
749 specifier\" depending on context. If this function does not suit your
750 exact need, you may be able to craft a particular solution using a
751 combination of DEFINED-TYPE-NAME-P and the TYPEXPAND functions.
753 The definition of \"valid type specifier\" employed by this function
754 is based on the following mnemonic:
756 \"Would TYPEP accept it as second argument?\"
758 Except that unlike TYPEP, this function fully supports compound
759 FUNCTION type specifiers, and the VALUES type specifier, too.
761 In particular, VALID-TYPE-SPECIFIER-P will return NIL if
762 TYPE-SPECIFIER is not a class, not a symbol that is known to name a
763 type specifier, and not a cons that represents a known compound type
764 specifier in a syntactically and recursively correct way.
766 Examples:
768 (valid-type-specifier-p '(cons * *)) => T
769 (valid-type-specifier-p '#:foo) => NIL
770 (valid-type-specifier-p '(cons * #:foo)) => NIL
771 (valid-type-specifier-p '(cons 1 *) => NIL
773 Experimental."
774 (declare (ignore env))
775 (handler-case (prog1 t (values-specifier-type type-specifier))
776 (parse-unknown-type () nil)
777 (error () nil)))
779 ;;; Note that the type NAME has been (re)defined, updating the
780 ;;; undefined warnings and VALUES-SPECIFIER-TYPE cache.
781 (defun %note-type-defined (name)
782 (declare (symbol name))
783 (note-name-defined name :type)
784 (values-specifier-type-cache-clear)
785 (values))
788 (!defun-from-collected-cold-init-forms !early-type-cold-init)