1 ;;;; This file contains the definition of non-CLASS types (e.g.
2 ;;;; subtypes of interesting BUILT-IN-CLASSes) and the interfaces to
3 ;;;; the type system. Common Lisp type specifiers are parsed into a
4 ;;;; somewhat canonical internal type representation that supports
5 ;;;; type union, intersection, etc. (Except that ALIEN types have
8 ;;;; This software is part of the SBCL system. See the README file for
11 ;;;; This software is derived from the CMU CL system, which was
12 ;;;; written at Carnegie Mellon University and released into the
13 ;;;; public domain. The software is in the public domain and is
14 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
15 ;;;; files for more information.
17 (in-package "SB!KERNEL")
19 (/show0
"late-type.lisp 19")
21 (!begin-collecting-cold-init-forms
)
23 ;;; ### Remaining incorrectnesses:
25 ;;; There are all sorts of nasty problems with open bounds on FLOAT
26 ;;; types (and probably FLOAT types in general.)
28 ;;; This condition is signalled whenever we make a UNKNOWN-TYPE so that
29 ;;; compiler warnings can be emitted as appropriate.
30 (define-condition parse-unknown-type
(condition)
31 ((specifier :reader parse-unknown-type-specifier
:initarg
:specifier
))
33 :specifier
(missing-arg)))
35 ;;; This condition is signalled whenever we encounter a type (DEFTYPE,
36 ;;; structure, condition, class) that has been marked as deprecated.
37 (define-condition parse-deprecated-type
(condition)
38 ((specifier :reader parse-deprecated-type-specifier
:initarg
:specifier
))
40 :specifier
(missing-arg)))
42 ;;; These functions are used as method for types which need a complex
43 ;;; subtypep method to handle some superclasses, but cover a subtree
44 ;;; of the type graph (i.e. there is no simple way for any other type
45 ;;; class to be a subtype.) There are always still complex ways,
46 ;;; namely UNION and MEMBER types, so we must give TYPE1's method a
47 ;;; chance to run, instead of immediately returning NIL, T.
48 (defun delegate-complex-subtypep-arg2 (type1 type2
)
50 (type-class-complex-subtypep-arg1 (type-class-info type1
))))
52 (funcall subtypep-arg1 type1 type2
)
54 (defun delegate-complex-intersection2 (type1 type2
)
55 (let ((method (type-class-complex-intersection2 (type-class-info type1
))))
56 (if (and method
(not (eq method
#'delegate-complex-intersection2
)))
57 (funcall method type2 type1
)
58 (hierarchical-intersection2 type1 type2
))))
60 (defun contains-unknown-type-p (ctype)
63 (compound-type (some #'contains-unknown-type-p
(compound-type-types ctype
)))
64 (negation-type (contains-unknown-type-p (negation-type-type ctype
)))
65 (cons-type (or (contains-unknown-type-p (cons-type-car-type ctype
))
66 (contains-unknown-type-p (cons-type-cdr-type ctype
))))
67 (array-type (contains-unknown-type-p (array-type-element-type ctype
)))
69 (or (some #'contains-unknown-type-p
(args-type-required ctype
))
70 (some #'contains-unknown-type-p
(args-type-optional ctype
))
71 (acond ((args-type-rest ctype
) (contains-unknown-type-p it
)))
72 (some (lambda (x) (contains-unknown-type-p (key-info-type x
)))
73 (args-type-keywords ctype
))
74 (and (fun-type-p ctype
)
75 (contains-unknown-type-p (fun-type-returns ctype
)))))))
77 ;; Similar to (NOT CONTAINS-UNKNOWN-TYPE-P), but report that (SATISFIES F)
78 ;; is not a testable type unless F is currently bound.
79 (defun testable-type-p (ctype)
81 (unknown-type nil
) ; must precede HAIRY because an unknown is HAIRY
83 (let ((spec (hairy-type-specifier ctype
)))
84 ;; Anything other than (SATISFIES ...) is testable
85 ;; because there's no reason to suppose that it isn't.
86 (or (neq (car spec
) 'satisfies
) (fboundp (cadr spec
)))))
87 (compound-type (every #'testable-type-p
(compound-type-types ctype
)))
88 (negation-type (testable-type-p (negation-type-type ctype
)))
89 (cons-type (and (testable-type-p (cons-type-car-type ctype
))
90 (testable-type-p (cons-type-cdr-type ctype
))))
91 ;; This case could be too strict. I think an array type is testable
92 ;; if the upgraded type is testable. Probably nobody cares though.
93 (array-type (testable-type-p (array-type-element-type ctype
)))
96 ;;; This is used by !DEFINE-SUPERCLASSES to define the SUBTYPE-ARG1
97 ;;; method. INFO is a list of conses
98 ;;; (SUPERCLASS-CLASS . {GUARD-TYPE-SPECIFIER | NIL}).
99 (defun has-superclasses-complex-subtypep-arg1 (type1 type2 info
)
100 ;; If TYPE2 might be concealing something related to our class
102 (if (type-might-contain-other-types-p type2
)
103 ;; too confusing, gotta punt
105 ;; ordinary case expected by old CMU CL code, where the taxonomy
106 ;; of TYPE2's representation accurately reflects the taxonomy of
107 ;; the underlying set
109 ;; FIXME: This old CMU CL code probably deserves a comment
110 ;; explaining to us mere mortals how it works...
111 (and (sb!xc
:typep type2
'classoid
)
113 (let ((guard (cdr x
)))
114 (when (or (not guard
)
115 (csubtypep type1
(if (%instancep guard
)
118 (specifier-type guard
)))))
120 (or (eq type2
(car x
))
121 (let ((inherits (layout-inherits
122 (classoid-layout (car x
)))))
123 (dotimes (i (length inherits
) nil
)
124 (when (eq type2
(layout-classoid (svref inherits i
)))
128 ;;; This function takes a list of specs, each of the form
129 ;;; (SUPERCLASS-NAME &OPTIONAL GUARD).
130 ;;; Consider one spec (with no guard): any instance of the named
131 ;;; TYPE-CLASS is also a subtype of the named superclass and of any of
132 ;;; its superclasses. If there are multiple specs, then some will have
133 ;;; guards. We choose the first spec whose guard is a supertype of
134 ;;; TYPE1 and use its superclass. In effect, a sequence of guards
137 ;;; G0,(and G1 (not G0)), (and G2 (not (or G0 G1))).
139 ;;; WHEN controls when the forms are executed.
140 (defmacro !define-superclasses
(type-class-name specs progn-oid
)
141 (let ((defun-name (symbolicate type-class-name
"-COMPLEX-SUBTYPEP-ARG1")))
143 (defun ,defun-name
(type1 type2
)
144 (has-superclasses-complex-subtypep-arg1
147 (list ,@(mapcar (lambda (spec)
148 (destructuring-bind (super &optional guard
) spec
149 `(cons (find-classoid ',super
) ',guard
)))
150 specs
)) #-sb-xc-host t
)))
152 (let ((type-class (type-class-or-lose ',type-class-name
)))
153 (setf (type-class-complex-subtypep-arg1 type-class
) #',defun-name
)
154 (setf (type-class-complex-subtypep-arg2 type-class
)
155 #'delegate-complex-subtypep-arg2
)
156 (setf (type-class-complex-intersection2 type-class
)
157 #'delegate-complex-intersection2
))))))
159 ;;;; FUNCTION and VALUES types
161 ;;;; Pretty much all of the general type operations are illegal on
162 ;;;; VALUES types, since we can't discriminate using them, do
163 ;;;; SUBTYPEP, etc. FUNCTION types are acceptable to the normal type
164 ;;;; operations, but are generally considered to be equivalent to
165 ;;;; FUNCTION. These really aren't true types in any type theoretic
166 ;;;; sense, but we still parse them into CTYPE structures for two
169 ;;;; -- Parsing and unparsing work the same way, and indeed we can't
170 ;;;; tell whether a type is a function or values type without
172 ;;;; -- Many of the places that can be annotated with real types can
173 ;;;; also be annotated with function or values types.
175 (!define-type-method
(values :simple-subtypep
:complex-subtypep-arg1
)
177 (declare (ignore type2
))
178 ;; FIXME: should be TYPE-ERROR, here and in next method
179 (error "SUBTYPEP is illegal on this type:~% ~S" (type-specifier type1
)))
181 (!define-type-method
(values :complex-subtypep-arg2
)
183 (declare (ignore type1
))
184 (error "SUBTYPEP is illegal on this type:~% ~S" (type-specifier type2
)))
186 (!define-type-method
(values :negate
) (type)
187 (error "NOT VALUES too confusing on ~S" (type-specifier type
)))
189 (!define-type-method
(values :unparse
) (type)
191 (let ((unparsed (unparse-args-types type
)))
192 (if (or (values-type-optional type
)
193 (values-type-rest type
)
194 (values-type-allowp type
))
196 (nconc unparsed
'(&optional
))))))
198 ;;; Return true if LIST1 and LIST2 have the same elements in the same
199 ;;; positions according to TYPE=. We return NIL, NIL if there is an
200 ;;; uncertain comparison.
201 (defun type=-list
(list1 list2
)
202 (declare (list list1 list2
))
203 (do ((types1 list1
(cdr types1
))
204 (types2 list2
(cdr types2
)))
205 ((or (null types1
) (null types2
))
206 (if (or types1 types2
)
209 (multiple-value-bind (val win
)
210 (type= (first types1
) (first types2
))
212 (return (values nil nil
)))
214 (return (values nil t
))))))
216 (!define-type-method
(values :simple-
=) (type1 type2
)
217 (type=-args type1 type2
))
219 ;;; a flag that we can bind to cause complex function types to be
220 ;;; unparsed as FUNCTION. This is useful when we want a type that we
221 ;;; can pass to TYPEP.
222 (!defvar
*unparse-fun-type-simplify
* nil
)
223 ;;; A flag to prevent TYPE-OF calls by user applications from returning
224 ;;; (NOT x). TYPE-SPECIFIER usually allows it to preserve information.
225 (!defvar
*unparse-allow-negation
* t
)
227 (!define-type-method
(function :negate
) (type) (make-negation-type type
))
229 (!define-type-method
(function :unparse
) (type)
230 (if *unparse-fun-type-simplify
*
233 (if (fun-type-wild-args type
)
235 (unparse-args-types type
))
237 (fun-type-returns type
)))))
239 ;;; The meaning of this is a little confused. On the one hand, all
240 ;;; function objects are represented the same way regardless of the
241 ;;; arglists and return values, and apps don't get to ask things like
242 ;;; (TYPEP #'FOO (FUNCTION (FIXNUM) *)) in any meaningful way. On the
243 ;;; other hand, Python wants to reason about function types. So...
244 (!define-type-method
(function :simple-subtypep
) (type1 type2
)
245 (flet ((fun-type-simple-p (type)
246 (not (or (fun-type-rest type
)
247 (fun-type-keyp type
))))
248 (every-csubtypep (types1 types2
)
252 do
(multiple-value-bind (res sure-p
)
254 (unless res
(return (values res sure-p
))))
255 finally
(return (values t t
)))))
256 (and/type
(values-subtypep (fun-type-returns type1
)
257 (fun-type-returns type2
))
258 (cond ((fun-type-wild-args type2
) (values t t
))
259 ((fun-type-wild-args type1
)
260 (cond ((fun-type-keyp type2
) (values nil nil
))
261 ((not (fun-type-rest type2
)) (values nil t
))
262 ((not (null (fun-type-required type2
)))
264 (t (and/type
(type= *universal-type
*
265 (fun-type-rest type2
))
270 ((not (and (fun-type-simple-p type1
)
271 (fun-type-simple-p type2
)))
273 (t (multiple-value-bind (min1 max1
) (fun-type-nargs type1
)
274 (multiple-value-bind (min2 max2
) (fun-type-nargs type2
)
275 (cond ((or (> max1 max2
) (< min1 min2
))
277 ((and (= min1 min2
) (= max1 max2
))
278 (and/type
(every-csubtypep
279 (fun-type-required type1
)
280 (fun-type-required type2
))
282 (fun-type-optional type1
)
283 (fun-type-optional type2
))))
286 (fun-type-required type1
)
287 (fun-type-optional type1
))
289 (fun-type-required type2
)
290 (fun-type-optional type2
))))))))))))
292 (!define-superclasses function
((function)) !cold-init-forms
)
294 ;;; The union or intersection of two FUNCTION types is FUNCTION.
295 (!define-type-method
(function :simple-union2
) (type1 type2
)
296 (declare (ignore type1 type2
))
297 (specifier-type 'function
))
298 (!define-type-method
(function :simple-intersection2
) (type1 type2
)
299 (let ((ftype (specifier-type 'function
)))
300 (cond ((eq type1 ftype
) type2
)
301 ((eq type2 ftype
) type1
)
302 (t (let ((rtype (values-type-intersection (fun-type-returns type1
)
303 (fun-type-returns type2
))))
304 (flet ((change-returns (ftype rtype
)
305 (declare (type fun-type ftype
) (type ctype rtype
))
306 (make-fun-type :required
(fun-type-required ftype
)
307 :optional
(fun-type-optional ftype
)
308 :keyp
(fun-type-keyp ftype
)
309 :keywords
(fun-type-keywords ftype
)
310 :allowp
(fun-type-allowp ftype
)
313 ((fun-type-wild-args type1
)
314 (if (fun-type-wild-args type2
)
315 (make-fun-type :wild-args t
317 (change-returns type2 rtype
)))
318 ((fun-type-wild-args type2
)
319 (change-returns type1 rtype
))
320 (t (multiple-value-bind (req opt rest
)
321 (args-type-op type1 type2
#'type-intersection
#'max
)
322 (make-fun-type :required req
326 :allowp
(and (fun-type-allowp type1
)
327 (fun-type-allowp type2
))
328 :returns rtype
))))))))))
330 ;;; The union or intersection of a subclass of FUNCTION with a
331 ;;; FUNCTION type is somewhat complicated.
332 (!define-type-method
(function :complex-intersection2
) (type1 type2
)
334 ((type= type1
(specifier-type 'function
)) type2
)
335 ((csubtypep type1
(specifier-type 'function
)) nil
)
336 (t :call-other-method
)))
337 (!define-type-method
(function :complex-union2
) (type1 type2
)
338 (declare (ignore type2
))
339 ;; TYPE2 is a FUNCTION type. If TYPE1 is a classoid type naming
340 ;; FUNCTION, then it is the union of the two; otherwise, there is no
343 ((type= type1
(specifier-type 'function
)) type1
)
346 (!define-type-method
(function :simple-
=) (type1 type2
)
347 (macrolet ((compare (comparator field
)
348 (let ((reader (symbolicate '#:fun-type- field
)))
349 `(,comparator
(,reader type1
) (,reader type2
)))))
350 (and/type
(compare type
= returns
)
351 (cond ((neq (fun-type-wild-args type1
) (fun-type-wild-args type2
))
353 ((eq (fun-type-wild-args type1
) t
)
355 (t (type=-args type1 type2
))))))
357 (!define-type-class constant
:inherits values
)
359 (!define-type-method
(constant :negate
) (type)
360 (error "NOT CONSTANT too confusing on ~S" (type-specifier type
)))
362 (!define-type-method
(constant :unparse
) (type)
363 `(constant-arg ,(type-specifier (constant-type-type type
))))
365 (!define-type-method
(constant :simple-
=) (type1 type2
)
366 (type= (constant-type-type type1
) (constant-type-type type2
)))
368 (!def-type-translator constant-arg
((:context context
) type
)
369 (make-constant-type :type
(single-value-specifier-type-r context type
)))
371 ;;; Return the lambda-list-like type specification corresponding
373 (declaim (ftype (function (args-type) list
) unparse-args-types
))
374 (defun unparse-args-types (type)
377 (dolist (arg (args-type-required type
))
378 (result (type-specifier arg
)))
380 (when (args-type-optional type
)
382 (dolist (arg (args-type-optional type
))
383 (result (type-specifier arg
))))
385 (when (args-type-rest type
)
387 (result (type-specifier (args-type-rest type
))))
389 (when (args-type-keyp type
)
391 (dolist (key (args-type-keywords type
))
392 (result (list (key-info-name key
)
393 (type-specifier (key-info-type key
))))))
395 (when (args-type-allowp type
)
396 (result '&allow-other-keys
))
400 (!def-type-translator function
((:context context
)
401 &optional
(args '*) (result '*))
402 (let ((result (coerce-to-values (values-specifier-type-r context result
))))
404 (if (eq result
*wild-type
*)
405 (specifier-type 'function
)
406 (make-fun-type :wild-args t
:returns result
))
407 (multiple-value-bind (llks required optional rest keywords
)
408 (parse-args-types context args
:function-type
)
409 (if (and (null required
)
411 (eq rest
*universal-type
*)
412 (not (ll-kwds-keyp llks
)))
413 (if (eq result
*wild-type
*)
414 (specifier-type 'function
)
415 (make-fun-type :wild-args t
:returns result
))
416 (make-fun-type :required required
419 :keyp
(ll-kwds-keyp llks
)
421 :allowp
(ll-kwds-allowp llks
)
422 :returns result
))))))
424 (!def-type-translator values
:list
((:context context
) &rest values
)
427 (multiple-value-bind (llks required optional rest
)
428 (parse-args-types context values
:values-type
)
430 (make-values-type :required required
:optional optional
:rest rest
)
431 (make-short-values-type required
)))))
433 ;;;; VALUES types interfaces
435 ;;;; We provide a few special operations that can be meaningfully used
436 ;;;; on VALUES types (as well as on any other type).
438 ;;; Return the minimum number of values possibly matching VALUES type
440 (defun values-type-min-value-count (type)
443 (ecase (named-type-name type
)
447 (length (values-type-required type
)))))
449 ;;; Return the maximum number of values possibly matching VALUES type
451 (defun values-type-max-value-count (type)
454 (ecase (named-type-name type
)
455 ((t *) call-arguments-limit
)
458 (if (values-type-rest type
)
460 (+ (length (values-type-optional type
))
461 (length (values-type-required type
)))))))
463 (defun values-type-may-be-single-value-p (type)
464 (<= (values-type-min-value-count type
)
466 (values-type-max-value-count type
)))
468 ;;; VALUES type with a single value.
469 (defun type-single-value-p (type)
470 (and (%values-type-p type
)
471 (not (values-type-rest type
))
472 (null (values-type-optional type
))
473 (singleton-p (values-type-required type
))))
475 ;;; Return the type of the first value indicated by TYPE. This is used
476 ;;; by people who don't want to have to deal with VALUES types.
477 #!-sb-fluid
(declaim (freeze-type values-type
))
478 ; (inline single-value-type))
479 (defun single-value-type (type)
480 (declare (type ctype type
))
481 (cond ((eq type
*wild-type
*)
483 ((eq type
*empty-type
*)
485 ((not (values-type-p type
))
487 ((car (args-type-required type
)))
488 (t (type-union (specifier-type 'null
)
489 (or (car (args-type-optional type
))
490 (args-type-rest type
)
491 (specifier-type 'null
))))))
493 ;;; Return the minimum number of arguments that a function can be
494 ;;; called with, and the maximum number or NIL. If not a function
495 ;;; type, return NIL, NIL.
496 (defun fun-type-nargs (type)
497 (declare (type ctype type
))
498 (if (and (fun-type-p type
) (not (fun-type-wild-args type
)))
499 (let ((fixed (length (args-type-required type
))))
500 (if (or (args-type-rest type
)
501 (args-type-keyp type
)
502 (args-type-allowp type
))
504 (values fixed
(+ fixed
(length (args-type-optional type
))))))
507 ;;; Determine whether TYPE corresponds to a definite number of values.
508 ;;; The first value is a list of the types for each value, and the
509 ;;; second value is the number of values. If the number of values is
510 ;;; not fixed, then return NIL and :UNKNOWN.
511 (defun values-types (type)
512 (declare (type ctype type
))
513 (cond ((or (eq type
*wild-type
*) (eq type
*empty-type
*))
514 (values nil
:unknown
))
515 ((or (args-type-optional type
)
516 (args-type-rest type
))
517 (values nil
:unknown
))
519 (let ((req (args-type-required type
)))
520 (values req
(length req
))))))
522 ;;; Return two values:
523 ;;; 1. A list of all the positional (fixed and optional) types.
524 ;;; 2. The &REST type (if any). If no &REST, then the DEFAULT-TYPE.
525 (defun values-type-types (type &optional
(default-type *empty-type
*))
526 (declare (type ctype type
))
527 (if (eq type
*wild-type
*)
528 (values nil
*universal-type
*)
529 (values (append (args-type-required type
)
530 (args-type-optional type
))
531 (or (args-type-rest type
)
534 ;;; types of values in (the <type> (values o_1 ... o_n))
535 (defun values-type-out (type count
)
536 (declare (type ctype type
) (type unsigned-byte count
))
537 (if (eq type
*wild-type
*)
538 (make-list count
:initial-element
*universal-type
*)
540 (flet ((process-types (types)
541 (loop for type in types
545 (process-types (values-type-required type
))
546 (process-types (values-type-optional type
))
547 (let ((rest (values-type-rest type
)))
553 ;;; types of variable in (m-v-bind (v_1 ... v_n) (the <type> ...
554 (defun values-type-in (type count
)
555 (declare (type ctype type
) (type unsigned-byte count
))
556 (if (eq type
*wild-type
*)
557 (make-list count
:initial-element
*universal-type
*)
559 (let ((null-type (specifier-type 'null
)))
560 (loop for type in
(values-type-required type
)
564 (loop for type in
(values-type-optional type
)
567 do
(res (type-union type null-type
)))
569 (loop with rest
= (acond ((values-type-rest type
)
570 (type-union it null-type
))
576 ;;; Return a list of OPERATION applied to the types in TYPES1 and
577 ;;; TYPES2, padding with REST2 as needed. TYPES1 must not be shorter
578 ;;; than TYPES2. The second value is T if OPERATION always returned a
579 ;;; true second value.
580 (defun fixed-values-op (types1 types2 rest2 operation
)
581 (declare (list types1 types2
) (type ctype rest2
) (type function operation
))
583 (values (mapcar (lambda (t1 t2
)
584 (multiple-value-bind (res win
)
585 (funcall operation t1 t2
)
591 (make-list (- (length types1
) (length types2
))
592 :initial-element rest2
)))
595 ;;; If TYPE isn't a values type, then make it into one.
596 (defun-cached (%coerce-to-values
:hash-bits
8 :hash-function
#'type-hash-value
)
598 (cond ((multiple-value-bind (res sure
)
599 (csubtypep (specifier-type 'null
) type
)
600 (and (not res
) sure
))
601 ;; FIXME: What should we do with (NOT SURE)?
602 (make-values-type :required
(list type
) :rest
*universal-type
*))
604 (make-values-type :optional
(list type
) :rest
*universal-type
*))))
606 (defun coerce-to-values (type)
607 (declare (type ctype type
))
608 (cond ((or (eq type
*universal-type
*)
609 (eq type
*wild-type
*))
611 ((values-type-p type
)
613 (t (%coerce-to-values type
))))
615 ;;; Return type, corresponding to ANSI short form of VALUES type
617 (defun make-short-values-type (types)
618 (declare (list types
))
619 (let ((last-required (position-if
621 (not/type
(csubtypep (specifier-type 'null
) type
)))
625 (make-values-type :required
(subseq types
0 (1+ last-required
))
626 :optional
(subseq types
(1+ last-required
))
627 :rest
*universal-type
*)
628 (make-values-type :optional types
:rest
*universal-type
*))))
630 (defun make-single-value-type (type)
631 (make-values-type :required
(list type
)))
633 ;;; Do the specified OPERATION on TYPE1 and TYPE2, which may be any
634 ;;; type, including VALUES types. With VALUES types such as:
637 ;;; we compute the more useful result
638 ;;; (VALUES (<operation> a0 b0) (<operation> a1 b1))
639 ;;; rather than the precise result
640 ;;; (<operation> (values a0 a1) (values b0 b1))
641 ;;; This has the virtue of always keeping the VALUES type specifier
642 ;;; outermost, and retains all of the information that is really
643 ;;; useful for static type analysis. We want to know what is always
644 ;;; true of each value independently. It is worthless to know that if
645 ;;; the first value is B0 then the second will be B1.
647 ;;; If the VALUES count signatures differ, then we produce a result with
648 ;;; the required VALUE count chosen by NREQ when applied to the number
649 ;;; of required values in TYPE1 and TYPE2. Any &KEY values become
650 ;;; &REST T (anyone who uses keyword values deserves to lose.)
652 ;;; The second value is true if the result is definitely empty or if
653 ;;; OPERATION returned true as its second value each time we called
654 ;;; it. Since we approximate the intersection of VALUES types, the
655 ;;; second value being true doesn't mean the result is exact.
656 (defun args-type-op (type1 type2 operation nreq
)
657 (declare (type ctype type1 type2
)
658 (type function operation nreq
))
659 (when (eq type1 type2
)
661 (multiple-value-bind (types1 rest1
)
662 (values-type-types type1
)
663 (multiple-value-bind (types2 rest2
)
664 (values-type-types type2
)
665 (multiple-value-bind (rest rest-exact
)
666 (funcall operation rest1 rest2
)
667 (multiple-value-bind (res res-exact
)
668 (if (< (length types1
) (length types2
))
669 (fixed-values-op types2 types1 rest1 operation
)
670 (fixed-values-op types1 types2 rest2 operation
))
671 (let* ((req (funcall nreq
672 (length (args-type-required type1
))
673 (length (args-type-required type2
))))
674 (required (subseq res
0 req
))
675 (opt (subseq res req
)))
676 (values required opt rest
677 (and rest-exact res-exact
))))))))
679 (defun values-type-op (type1 type2 operation nreq
)
680 (multiple-value-bind (required optional rest exactp
)
681 (args-type-op type1 type2 operation nreq
)
682 (values (make-values-type :required required
687 (defun compare-key-args (type1 type2
)
688 (let ((keys1 (args-type-keywords type1
))
689 (keys2 (args-type-keywords type2
)))
690 (and (= (length keys1
) (length keys2
))
691 (eq (args-type-allowp type1
)
692 (args-type-allowp type2
))
693 (loop for key1 in keys1
694 for match
= (find (key-info-name key1
)
695 keys2
:key
#'key-info-name
)
697 (type= (key-info-type key1
)
698 (key-info-type match
)))))))
700 (defun type=-args
(type1 type2
)
701 (macrolet ((compare (comparator field
)
702 (let ((reader (symbolicate '#:args-type- field
)))
703 `(,comparator
(,reader type1
) (,reader type2
)))))
705 (cond ((null (args-type-rest type1
))
706 (values (null (args-type-rest type2
)) t
))
707 ((null (args-type-rest type2
))
710 (compare type
= rest
)))
711 (and/type
(and/type
(compare type
=-list required
)
712 (compare type
=-list optional
))
713 (if (or (args-type-keyp type1
) (args-type-keyp type2
))
714 (values (compare-key-args type1 type2
) t
)
717 ;;; Do a union or intersection operation on types that might be values
718 ;;; types. The result is optimized for utility rather than exactness,
719 ;;; but it is guaranteed that it will be no smaller (more restrictive)
720 ;;; than the precise result.
722 ;;; The return convention seems to be analogous to
723 ;;; TYPES-EQUAL-OR-INTERSECT. -- WHN 19990910.
724 (defun-cached (values-type-union :hash-function
#'type-cache-hash
726 ((type1 eq
) (type2 eq
))
727 (declare (type ctype type1 type2
))
728 (cond ((or (eq type1
*wild-type
*) (eq type2
*wild-type
*)) *wild-type
*)
729 ((eq type1
*empty-type
*) type2
)
730 ((eq type2
*empty-type
*) type1
)
732 (values (values-type-op type1 type2
#'type-union
#'min
)))))
734 (defun-cached (values-type-intersection :hash-function
#'type-cache-hash
736 ((type1 eq
) (type2 eq
))
737 (declare (type ctype type1 type2
))
738 (cond ((eq type1
*wild-type
*)
739 (coerce-to-values type2
))
740 ((or (eq type2
*wild-type
*) (eq type2
*universal-type
*))
742 ((or (eq type1
*empty-type
*) (eq type2
*empty-type
*))
744 ((and (not (values-type-p type2
))
745 (values-type-required type1
))
746 (let ((req1 (values-type-required type1
)))
747 (make-values-type :required
(cons (type-intersection (first req1
) type2
)
749 :optional
(values-type-optional type1
)
750 :rest
(values-type-rest type1
)
751 :allowp
(values-type-allowp type1
))))
753 (values (values-type-op type1
(coerce-to-values type2
)
757 ;;; This is like TYPES-EQUAL-OR-INTERSECT, except that it sort of
758 ;;; works on VALUES types. Note that due to the semantics of
759 ;;; VALUES-TYPE-INTERSECTION, this might return (VALUES T T) when
760 ;;; there isn't really any intersection.
761 (defun values-types-equal-or-intersect (type1 type2
)
762 (cond ((or (eq type1
*empty-type
*) (eq type2
*empty-type
*))
764 ((or (eq type1
*wild-type
*) (eq type2
*wild-type
*))
767 (let ((res (values-type-intersection type1 type2
)))
768 (values (not (eq res
*empty-type
*))
771 ;;; a SUBTYPEP-like operation that can be used on any types, including
773 (defun-cached (values-subtypep :hash-function
#'type-cache-hash
776 ((type1 eq
) (type2 eq
))
777 (declare (type ctype type1 type2
))
778 (cond ((or (eq type2
*wild-type
*) (eq type2
*universal-type
*)
779 (eq type1
*empty-type
*))
781 ((eq type1
*wild-type
*)
782 (values (eq type2
*wild-type
*) t
))
783 ((or (eq type2
*empty-type
*)
784 (not (values-types-equal-or-intersect type1 type2
)))
786 ((and (not (values-type-p type2
))
787 (values-type-required type1
))
788 (csubtypep (first (values-type-required type1
))
790 (t (setq type2
(coerce-to-values type2
))
791 (multiple-value-bind (types1 rest1
) (values-type-types type1
)
792 (multiple-value-bind (types2 rest2
) (values-type-types type2
)
793 (cond ((< (length (values-type-required type1
))
794 (length (values-type-required type2
)))
796 ((< (length types1
) (length types2
))
799 (do ((t1 types1
(rest t1
))
800 (t2 types2
(rest t2
)))
802 (csubtypep rest1 rest2
))
803 (multiple-value-bind (res win-p
)
804 (csubtypep (first t1
) (first t2
))
806 (return (values nil nil
)))
808 (return (values nil t
))))))))))))
810 ;;;; type method interfaces
812 ;;; like SUBTYPEP, only works on CTYPE structures
813 (defun-cached (csubtypep :hash-function
#'type-cache-hash
817 ((type1 eq
) (type2 eq
))
818 (declare (type ctype type1 type2
))
819 (cond ((or (eq type1 type2
)
820 (eq type1
*empty-type
*)
821 (eq type2
*universal-type
*))
824 ((eq type1
*universal-type
*)
828 (!invoke-type-method
:simple-subtypep
:complex-subtypep-arg2
830 :complex-arg1
:complex-subtypep-arg1
)))))
832 ;;; Just parse the type specifiers and call CSUBTYPE.
833 (defun sb!xc
:subtypep
(type1 type2
&optional environment
)
834 "Return two values indicating the relationship between type1 and type2.
835 If values are T and T, type1 definitely is a subtype of type2.
836 If values are NIL and T, type1 definitely is not a subtype of type2.
837 If values are NIL and NIL, it couldn't be determined."
838 (declare (type lexenv-designator environment
) (ignore environment
))
839 (declare (explicit-check))
840 (csubtypep (specifier-type type1
) (specifier-type type2
)))
842 ;;; If two types are definitely equivalent, return true. The second
843 ;;; value indicates whether the first value is definitely correct.
844 ;;; This should only fail in the presence of HAIRY types.
845 (defun-cached (type= :hash-function
#'type-cache-hash
849 ((type1 eq
) (type2 eq
))
850 (declare (type ctype type1 type2
))
851 (cond ((eq type1 type2
)
853 ;; If args are not EQ, but both allow TYPE= optimization,
854 ;; and at least one is interned, then return no and certainty.
855 ;; Most of the interned CTYPEs admit this optimization,
856 ;; NUMERIC and MEMBER types do as well.
857 ((and (minusp (logior (type-hash-value type1
) (type-hash-value type2
)))
858 (logtest (logand (type-hash-value type1
) (type-hash-value type2
))
859 +type-admits-type
=-optimization
+))
862 (memoize (!invoke-type-method
:simple-
= :complex-
= type1 type2
)))))
864 ;;; Not exactly the negation of TYPE=, since when the relationship is
865 ;;; uncertain, we still return NIL, NIL. This is useful in cases where
866 ;;; the conservative assumption is =.
867 (defun type/= (type1 type2
)
868 (declare (type ctype type1 type2
))
869 (multiple-value-bind (res win
) (type= type1 type2
)
874 ;;; the type method dispatch case of TYPE-UNION2
875 (defun %type-union2
(type1 type2
)
876 ;; As in %TYPE-INTERSECTION2, it seems to be a good idea to give
877 ;; both argument orders a chance at COMPLEX-INTERSECTION2. Unlike
878 ;; %TYPE-INTERSECTION2, though, I don't have a specific case which
879 ;; demonstrates this is actually necessary. Also unlike
880 ;; %TYPE-INTERSECTION2, there seems to be no need to distinguish
881 ;; between not finding a method and having a method return NIL.
883 (!invoke-type-method
:simple-union2
:complex-union2
886 (declare (inline 1way
))
887 (or (1way type1 type2
)
888 (1way type2 type1
))))
890 ;;; Find a type which includes both types. Any inexactness is
891 ;;; represented by the fuzzy element types; we return a single value
892 ;;; that is precise to the best of our knowledge. This result is
893 ;;; simplified into the canonical form, thus is not a UNION-TYPE
894 ;;; unless we find no other way to represent the result.
895 (defun-cached (type-union2 :hash-function
#'type-cache-hash
898 ((type1 eq
) (type2 eq
))
899 ;; KLUDGE: This was generated from TYPE-INTERSECTION2 by Ye Olde Cut And
900 ;; Paste technique of programming. If it stays around (as opposed to
901 ;; e.g. fading away in favor of some CLOS solution) the shared logic
902 ;; should probably become shared code. -- WHN 2001-03-16
903 (declare (type ctype type1 type2
))
909 ;; CSUBTYPEP for array-types answers questions about the
910 ;; specialized type, yet for union we want to take the
911 ;; expressed type in account too.
912 ((and (not (and (array-type-p type1
) (array-type-p type2
)))
913 (or (setf t2
(csubtypep type1 type2
))
914 (csubtypep type2 type1
)))
916 ((or (union-type-p type1
)
917 (union-type-p type2
))
918 ;; Unions of UNION-TYPE should have the UNION-TYPE-TYPES
919 ;; values broken out and united separately. The full TYPE-UNION
920 ;; function knows how to do this, so let it handle it.
921 (type-union type1 type2
))
923 ;; the ordinary case: we dispatch to type methods
924 (%type-union2 type1 type2
)))))))
926 ;;; the type method dispatch case of TYPE-INTERSECTION2
927 (defun %type-intersection2
(type1 type2
)
928 ;; We want to give both argument orders a chance at
929 ;; COMPLEX-INTERSECTION2. Without that, the old CMU CL type
930 ;; methods could give noncommutative results, e.g.
931 ;; (TYPE-INTERSECTION2 *EMPTY-TYPE* SOME-HAIRY-TYPE)
933 ;; (TYPE-INTERSECTION2 SOME-HAIRY-TYPE *EMPTY-TYPE*)
934 ;; => #<NAMED-TYPE NIL>, T
935 ;; We also need to distinguish between the case where we found a
936 ;; type method, and it returned NIL, and the case where we fell
937 ;; through without finding any type method. An example of the first
938 ;; case is the intersection of a HAIRY-TYPE with some ordinary type.
939 ;; An example of the second case is the intersection of two
940 ;; completely-unrelated types, e.g. CONS and NUMBER, or SYMBOL and
943 ;; (Why yes, CLOS probably *would* be nicer..)
945 (!invoke-type-method
:simple-intersection2
:complex-intersection2
947 :default
:call-other-method
)))
948 (declare (inline 1way
))
949 (let ((xy (1way type1 type2
)))
950 (or (and (not (eql xy
:call-other-method
)) xy
)
951 (let ((yx (1way type2 type1
)))
952 (or (and (not (eql yx
:call-other-method
)) yx
)
953 (cond ((and (eql xy
:call-other-method
)
954 (eql yx
:call-other-method
))
959 (defun-cached (type-intersection2 :hash-function
#'type-cache-hash
963 ((type1 eq
) (type2 eq
))
964 (declare (type ctype type1 type2
))
966 ;; FIXME: For some reason, this doesn't catch e.g. type1 =
967 ;; type2 = (SPECIFIER-TYPE
968 ;; 'SOME-UNKNOWN-TYPE). Investigate. - CSR, 2002-04-10
972 ((or (intersection-type-p type1
)
973 (intersection-type-p type2
))
974 ;; Intersections of INTERSECTION-TYPE should have the
975 ;; INTERSECTION-TYPE-TYPES values broken out and intersected
976 ;; separately. The full TYPE-INTERSECTION function knows how
977 ;; to do that, so let it handle it.
978 (type-intersection type1 type2
))
980 ;; the ordinary case: we dispatch to type methods
981 (%type-intersection2 type1 type2
))))))
983 ;;; Return as restrictive and simple a type as we can discover that is
984 ;;; no more restrictive than the intersection of TYPE1 and TYPE2. At
985 ;;; worst, we arbitrarily return one of the arguments as the first
986 ;;; value (trying not to return a hairy type).
987 (defun type-approx-intersection2 (type1 type2
)
988 (cond ((type-intersection2 type1 type2
))
989 ((hairy-type-p type1
) type2
)
992 ;;; a test useful for checking whether a derived type matches a
995 ;;; The first value is true unless the types don't intersect and
996 ;;; aren't equal. The second value is true if the first value is
997 ;;; definitely correct. NIL is considered to intersect with any type.
998 ;;; If T is a subtype of either type, then we also return T, T. This
999 ;;; way we recognize that hairy types might intersect with T.
1001 ;;; Well now given the statement above that this is "useful for ..."
1002 ;;; a particular thing, I see how treating *empty-type* magically could
1003 ;;; be useful, however given all the _other_ calls to this function within
1004 ;;; this file, it seems suboptimal, because logically it is wrong.
1005 (defun types-equal-or-intersect (type1 type2
)
1006 (declare (type ctype type1 type2
))
1007 (if (or (eq type1
*empty-type
*) (eq type2
*empty-type
*))
1009 (let ((intersection2 (type-intersection2 type1 type2
)))
1010 (cond ((not intersection2
)
1011 (if (or (csubtypep *universal-type
* type1
)
1012 (csubtypep *universal-type
* type2
))
1015 ((eq intersection2
*empty-type
*) (values nil t
))
1016 (t (values t t
))))))
1018 ;;; Return a Common Lisp type specifier corresponding to the TYPE
1020 (defun type-specifier (type)
1021 (declare (type ctype type
))
1022 (funcall (type-class-unparse (type-class-info type
)) type
))
1024 ;;; Don't try to define a print method until it's actually gonna work!
1025 ;;; (Otherwise this would be near the DEFSTRUCT)
1026 (defmethod print-object ((ctype ctype
) stream
)
1027 (print-unreadable-object (ctype stream
:type t
)
1028 (prin1 (type-specifier ctype
) stream
)))
1031 ;;; Just dump it as a specifier. (We'll convert it back upon loading.)
1032 (defmethod make-load-form ((type ctype
) &optional env
)
1033 (declare (ignore env
))
1034 `(specifier-type ',(type-specifier type
)))
1036 (defun-cached (type-negation :hash-function
#'type-hash-value
1040 (declare (type ctype type
))
1041 (funcall (type-class-negate (type-class-info type
)) type
))
1043 (defun-cached (type-singleton-p :hash-function
#'type-hash-value
1047 (declare (type ctype type
))
1048 (let ((function (type-class-singleton-p (type-class-info type
))))
1050 (funcall function type
)
1053 ;;; (VALUES-SPECIFIER-TYPE and SPECIFIER-TYPE moved from here to
1054 ;;; early-type.lisp by WHN ca. 19990201.)
1056 ;;; Take a list of type specifiers, computing the translation of each
1057 ;;; specifier and defining it as a builtin type.
1058 ;;; Seee the comments in 'type-init' for why this is a slightly
1059 ;;; screwy way to go about it.
1060 (declaim (ftype (function (list) (values)) !precompute-types
))
1061 (defun !precompute-types
(specs)
1062 (dolist (spec specs
)
1063 (let ((res (handler-bind
1064 ((parse-unknown-type
1066 (declare (ignore c
))
1067 ;; We can handle conditions at this point,
1068 ;; but win32 can not perform i/o here because
1069 ;; !MAKE-COLD-STDERR-STREAM has no implementation.
1071 (progn (write-string "//caught: parse-unknown ")
1074 (specifier-type spec
))))
1075 (unless (unknown-type-p res
)
1076 (setf (info :type
:builtin spec
) res
)
1077 (setf (info :type
:kind spec
) :primitive
))))
1080 ;;;; general TYPE-UNION and TYPE-INTERSECTION operations
1082 ;;;; These are fully general operations on CTYPEs: they'll always
1083 ;;;; return a CTYPE representing the result.
1085 ;;; shared logic for unions and intersections: Return a list of
1086 ;;; types representing the same types as INPUT-TYPES, but with
1087 ;;; COMPOUND-TYPEs satisfying %COMPOUND-TYPE-P broken up into their
1088 ;;; component types, and with any SIMPLY2 simplifications applied.
1090 ((def (name compound-type-p simplify2
)
1091 `(defun ,name
(types)
1093 (multiple-value-bind (first rest
)
1094 (if (,compound-type-p
(car types
))
1095 (values (car (compound-type-types (car types
)))
1096 (append (cdr (compound-type-types (car types
)))
1098 (values (car types
) (cdr types
)))
1099 (let ((rest (,name rest
)) u
)
1100 (dolist (r rest
(cons first rest
))
1101 (when (setq u
(,simplify2 first r
))
1102 (return (,name
(nsubstitute u r rest
)))))))))))
1103 (def simplify-intersections intersection-type-p type-intersection2
)
1104 (def simplify-unions union-type-p type-union2
))
1106 (defun maybe-distribute-one-union (union-type types
)
1107 (let* ((intersection (apply #'type-intersection types
))
1108 (union (mapcar (lambda (x) (type-intersection x intersection
))
1109 (union-type-types union-type
))))
1110 (if (notany (lambda (x) (or (hairy-type-p x
)
1111 (intersection-type-p x
)))
1116 (defun type-intersection (&rest input-types
)
1117 (%type-intersection input-types
))
1118 (defun-cached (%type-intersection
:hash-bits
10 :hash-function
#'type-list-cache-hash
)
1119 ((input-types equal
))
1120 (let ((simplified-types (simplify-intersections input-types
)))
1121 (declare (type list simplified-types
))
1122 ;; We want to have a canonical representation of types (or failing
1123 ;; that, punt to HAIRY-TYPE). Canonical representation would have
1124 ;; intersections inside unions but not vice versa, since you can
1125 ;; always achieve that by the distributive rule. But we don't want
1126 ;; to just apply the distributive rule, since it would be too easy
1127 ;; to end up with unreasonably huge type expressions. So instead
1128 ;; we try to generate a simple type by distributing the union; if
1129 ;; the type can't be made simple, we punt to HAIRY-TYPE.
1130 (if (and (cdr simplified-types
) (some #'union-type-p simplified-types
))
1131 (let* ((first-union (find-if #'union-type-p simplified-types
))
1132 (other-types (coerce (remove first-union simplified-types
)
1134 (distributed (maybe-distribute-one-union first-union
1137 (apply #'type-union distributed
)
1138 (%make-hairy-type
`(and ,@(map 'list
#'type-specifier
1139 simplified-types
)))))
1141 ((null simplified-types
) *universal-type
*)
1142 ((null (cdr simplified-types
)) (car simplified-types
))
1143 (t (%make-intersection-type
1144 (some #'type-enumerable simplified-types
)
1145 simplified-types
))))))
1147 (defun type-union (&rest input-types
)
1148 (%type-union input-types
))
1149 (defun-cached (%type-union
:hash-bits
8 :hash-function
#'type-list-cache-hash
)
1150 ((input-types equal
))
1151 (let ((simplified-types (simplify-unions input-types
)))
1153 ((null simplified-types
) *empty-type
*)
1154 ((null (cdr simplified-types
)) (car simplified-types
))
1156 (every #'type-enumerable simplified-types
)
1157 simplified-types
)))))
1161 (!define-type-method
(named :simple-
=) (type1 type2
)
1162 ;;(aver (not (eq type1 *wild-type*))) ; * isn't really a type.
1163 (values (eq type1 type2
) t
))
1165 (defun cons-type-might-be-empty-type (type)
1166 (declare (type cons-type type
))
1167 (let ((car-type (cons-type-car-type type
))
1168 (cdr-type (cons-type-cdr-type type
)))
1170 (if (cons-type-p car-type
)
1171 (cons-type-might-be-empty-type car-type
)
1172 (multiple-value-bind (yes surep
)
1173 (type= car-type
*empty-type
*)
1176 (if (cons-type-p cdr-type
)
1177 (cons-type-might-be-empty-type cdr-type
)
1178 (multiple-value-bind (yes surep
)
1179 (type= cdr-type
*empty-type
*)
1183 (defun cons-type-length-info (type)
1184 (declare (type cons-type type
))
1185 (do ((min 1 (1+ min
))
1186 (cdr (cons-type-cdr-type type
) (cons-type-cdr-type cdr
)))
1187 ((not (cons-type-p cdr
))
1189 ((csubtypep cdr
(specifier-type 'null
))
1191 ((csubtypep *universal-type
* cdr
)
1193 ((type/= (type-intersection (specifier-type 'cons
) cdr
) *empty-type
*)
1195 ((type/= (type-intersection (specifier-type 'null
) cdr
) *empty-type
*)
1197 (t (values min
:maybe
))))
1200 (!define-type-method
(named :complex-
=) (type1 type2
)
1202 ((and (eq type2
*empty-type
*)
1203 (or (and (intersection-type-p type1
)
1204 ;; not allowed to be unsure on these... FIXME: keep
1205 ;; the list of CL types that are intersection types
1206 ;; once and only once.
1207 (not (or (type= type1
(specifier-type 'ratio
))
1208 (type= type1
(specifier-type 'keyword
)))))
1209 (and (cons-type-p type1
)
1210 (cons-type-might-be-empty-type type1
))))
1211 ;; things like (AND (EQL 0) (SATISFIES ODDP)) or (AND FUNCTION
1212 ;; STREAM) can get here. In general, we can't really tell
1213 ;; whether these are equal to NIL or not, so
1215 ((type-might-contain-other-types-p type1
)
1216 (invoke-complex-=-other-method type1 type2
))
1217 (t (values nil t
))))
1219 (!define-type-method
(named :simple-subtypep
) (type1 type2
)
1220 (aver (not (eq type1
*wild-type
*))) ; * isn't really a type.
1221 (aver (not (eq type1 type2
)))
1222 (values (or (eq type1
*empty-type
*)
1223 (eq type2
*wild-type
*)
1224 (eq type2
*universal-type
*)) t
))
1226 (!define-type-method
(named :complex-subtypep-arg1
) (type1 type2
)
1227 ;; This AVER causes problems if we write accurate methods for the
1228 ;; union (and possibly intersection) types which then delegate to
1229 ;; us; while a user shouldn't get here, because of the odd status of
1230 ;; *wild-type* a type-intersection executed by the compiler can. -
1233 ;; (aver (not (eq type1 *wild-type*))) ; * isn't really a type.
1234 (cond ((eq type1
*empty-type
*)
1236 (;; When TYPE2 might be the universal type in disguise
1237 (type-might-contain-other-types-p type2
)
1238 ;; Now that the UNION and HAIRY COMPLEX-SUBTYPEP-ARG2 methods
1239 ;; can delegate to us (more or less as CALL-NEXT-METHOD) when
1240 ;; they're uncertain, we can't just barf on COMPOUND-TYPE and
1241 ;; HAIRY-TYPEs as we used to. Instead we deal with the
1242 ;; problem (where at least part of the problem is cases like
1243 ;; (SUBTYPEP T '(SATISFIES FOO))
1245 ;; (SUBTYPEP T '(AND (SATISFIES FOO) (SATISFIES BAR)))
1246 ;; where the second type is a hairy type like SATISFIES, or
1247 ;; is a compound type which might contain a hairy type) by
1248 ;; returning uncertainty.
1250 ((eq type1
*funcallable-instance-type
*)
1251 (values (eq type2
(specifier-type 'function
)) t
))
1253 ;; This case would have been picked off by the SIMPLE-SUBTYPEP
1254 ;; method, and so shouldn't appear here.
1255 (aver (not (named-type-p type2
)))
1256 ;; Since TYPE2 is not EQ *UNIVERSAL-TYPE* and is not another
1257 ;; named type in disguise, TYPE2 is not a superset of TYPE1.
1260 (!define-type-method
(named :complex-subtypep-arg2
) (type1 type2
)
1261 (aver (not (eq type2
*wild-type
*))) ; * isn't really a type.
1262 (cond ((eq type2
*universal-type
*)
1264 ;; some CONS types can conceal danger
1265 ((and (cons-type-p type1
) (cons-type-might-be-empty-type type1
))
1267 ((type-might-contain-other-types-p type1
)
1268 ;; those types can be other types in disguise. So we'd
1270 (invoke-complex-subtypep-arg1-method type1 type2
))
1271 ((and (or (eq type2
*instance-type
*)
1272 (eq type2
*funcallable-instance-type
*))
1273 (member-type-p type1
))
1274 ;; member types can be subtypep INSTANCE and
1275 ;; FUNCALLABLE-INSTANCE in surprising ways.
1276 (invoke-complex-subtypep-arg1-method type1 type2
))
1277 ((and (eq type2
*extended-sequence-type
*) (classoid-p type1
))
1278 (values (if (classoid-inherits-from type1
'sequence
) t nil
) t
))
1279 ((and (eq type2
*instance-type
*) (classoid-p type1
))
1281 ((classoid-non-instance-p type1
)
1283 ((classoid-inherits-from type1
'function
)
1285 ((eq type1
(find-classoid 'function
))
1287 ((or (structure-classoid-p type1
)
1288 (condition-classoid-p type1
))
1290 (t (values nil nil
))))
1291 ((and (eq type2
*funcallable-instance-type
*) (classoid-p type1
))
1292 (if (and (not (classoid-non-instance-p type1
))
1293 (classoid-inherits-from type1
'function
))
1297 ;; FIXME: This seems to rely on there only being 4 or 5
1298 ;; NAMED-TYPE values, and the exclusion of various
1299 ;; possibilities above. It would be good to explain it and/or
1300 ;; rewrite it so that it's clearer.
1303 (!define-type-method
(named :simple-intersection2
) (type1 type2
)
1305 ((and (eq type1
*extended-sequence-type
*)
1306 (or (eq type2
*instance-type
*)
1307 (eq type2
*funcallable-instance-type
*)))
1309 ((and (or (eq type1
*instance-type
*)
1310 (eq type1
*funcallable-instance-type
*))
1311 (eq type2
*extended-sequence-type
*))
1314 (hierarchical-intersection2 type1 type2
))))
1316 (!define-type-method
(named :complex-intersection2
) (type1 type2
)
1317 ;; FIXME: This assertion failed when I added it in sbcl-0.6.11.13.
1318 ;; Perhaps when bug 85 is fixed it can be reenabled.
1319 ;;(aver (not (eq type2 *wild-type*))) ; * isn't really a type.
1320 (flet ((empty-unless-hairy (type)
1321 (unless (or (type-might-contain-other-types-p type
)
1322 (member-type-p type
))
1325 ((eq type2
*extended-sequence-type
*)
1327 ((or structure-classoid condition-classoid
) *empty-type
*)
1329 ((classoid-non-instance-p type1
) *empty-type
*)
1330 ((classoid-inherits-from type1
'sequence
) type1
)))
1331 (t (empty-unless-hairy type1
))))
1332 ((eq type2
*instance-type
*)
1334 ((or structure-classoid condition-classoid
) type1
)
1335 (classoid (when (or (classoid-non-instance-p type1
)
1336 (eq type1
(find-classoid 'function
))
1337 (classoid-inherits-from type1
'function
))
1339 (t (empty-unless-hairy type1
))))
1340 ((eq type2
*funcallable-instance-type
*)
1342 ((or structure-classoid condition-classoid
) *empty-type
*)
1345 ((classoid-non-instance-p type1
) *empty-type
*)
1346 ((classoid-inherits-from type1
'function
) type1
)
1347 ((type= type1
(find-classoid 'function
)) type2
)))
1349 (t (empty-unless-hairy type1
))))
1350 (t (hierarchical-intersection2 type1 type2
)))))
1352 (!define-type-method
(named :complex-union2
) (type1 type2
)
1353 ;; Perhaps when bug 85 is fixed this can be reenabled.
1354 ;;(aver (not (eq type2 *wild-type*))) ; * isn't really a type.
1356 ((eq type2
*extended-sequence-type
*)
1357 (cond ((not (classoid-p type1
)) nil
)
1358 ((and (not (classoid-non-instance-p type1
))
1359 (classoid-inherits-from type1
'sequence
))
1361 ((eq type2
*instance-type
*)
1362 (cond ((not (classoid-p type1
)) nil
)
1363 ((and (not (classoid-non-instance-p type1
))
1364 (not (classoid-inherits-from type1
'function
)))
1366 ((eq type2
*funcallable-instance-type
*)
1367 (cond ((not (classoid-p type1
)) nil
)
1368 ((classoid-non-instance-p type1
) nil
)
1369 ((not (classoid-inherits-from type1
'function
)) nil
)
1370 ((eq type1
(specifier-type 'function
)) type1
)
1372 (t (hierarchical-union2 type1 type2
))))
1374 (!define-type-method
(named :negate
) (x)
1375 (aver (not (eq x
*wild-type
*)))
1377 ((eq x
*universal-type
*) *empty-type
*)
1378 ((eq x
*empty-type
*) *universal-type
*)
1379 ((or (eq x
*instance-type
*)
1380 (eq x
*funcallable-instance-type
*)
1381 (eq x
*extended-sequence-type
*))
1382 (make-negation-type x
))
1383 (t (bug "NAMED type unexpected: ~S" x
))))
1385 (!define-type-method
(named :unparse
) (x)
1386 (named-type-name x
))
1388 ;;;; hairy and unknown types
1389 ;;;; DEFINE-TYPE-CLASS HAIRY is in 'early-type'
1391 (!define-type-method
(hairy :negate
) (x) (make-negation-type x
))
1393 (!define-type-method
(hairy :unparse
) (x)
1394 (hairy-type-specifier x
))
1396 (!define-type-method
(hairy :simple-subtypep
) (type1 type2
)
1397 (let ((hairy-spec1 (hairy-type-specifier type1
))
1398 (hairy-spec2 (hairy-type-specifier type2
)))
1399 (cond ((equal-but-no-car-recursion hairy-spec1 hairy-spec2
)
1401 ((maybe-reparse-specifier! type1
)
1402 (csubtypep type1 type2
))
1403 ((maybe-reparse-specifier! type2
)
1404 (csubtypep type1 type2
))
1406 (values nil nil
)))))
1408 (!define-type-method
(hairy :complex-subtypep-arg2
) (type1 type2
)
1409 (if (maybe-reparse-specifier! type2
)
1410 (csubtypep type1 type2
)
1411 (let ((specifier (hairy-type-specifier type2
)))
1412 (cond ((and (consp specifier
) (eql (car specifier
) 'satisfies
))
1413 (case (cadr specifier
)
1414 ((keywordp) (if (type= type1
(specifier-type 'symbol
))
1416 (invoke-complex-subtypep-arg1-method type1 type2
)))
1417 (t (invoke-complex-subtypep-arg1-method type1 type2
))))
1419 (invoke-complex-subtypep-arg1-method type1 type2
))))))
1421 (!define-type-method
(hairy :complex-subtypep-arg1
) (type1 type2
)
1422 (if (maybe-reparse-specifier! type1
)
1423 (csubtypep type1 type2
)
1426 (!define-type-method
(hairy :complex-
=) (type1 type2
)
1427 (if (maybe-reparse-specifier! type2
)
1431 (!define-type-method
(hairy :simple-intersection2
:complex-intersection2
)
1433 (acond ((type= type1 type2
)
1435 ((eq type2
(literal-ctype *satisfies-keywordp-type
*))
1436 ;; (AND (MEMBER A) (SATISFIES KEYWORDP)) is possibly non-empty
1437 ;; if A is re-homed as :A. However as a special case that really
1438 ;; does occur, (AND (MEMBER NIL) (SATISFIES KEYWORDP))
1439 ;; is empty because of the illegality of changing NIL's package.
1440 (if (eq type1
(specifier-type 'null
))
1442 (multiple-value-bind (answer certain
)
1443 (types-equal-or-intersect type1
(specifier-type 'symbol
))
1444 (and (not answer
) certain
*empty-type
*))))
1445 ((eq type2
(literal-ctype *fun-name-type
*))
1446 (multiple-value-bind (answer certain
)
1447 (types-equal-or-intersect type1
(specifier-type 'symbol
))
1450 (multiple-value-bind (answer certain
)
1451 (types-equal-or-intersect type1
(specifier-type 'cons
))
1452 (and (not answer
) certain
*empty-type
*)))))
1453 ((and (typep (hairy-type-specifier type2
) '(cons (eql satisfies
)))
1454 (info :function
:predicate-truth-constraint
1455 (cadr (hairy-type-specifier type2
))))
1456 (multiple-value-bind (answer certain
)
1457 (types-equal-or-intersect type1
(specifier-type it
))
1458 (and (not answer
) certain
*empty-type
*)))))
1460 (!define-type-method
(hairy :simple-union2
)
1462 (if (type= type1 type2
)
1466 (!define-type-method
(hairy :simple-
=) (type1 type2
)
1467 (if (equal-but-no-car-recursion (hairy-type-specifier type1
)
1468 (hairy-type-specifier type2
))
1472 (!def-type-translator satisfies
:list
(&whole whole predicate-name
)
1473 (unless (symbolp predicate-name
)
1474 (error 'simple-type-error
1475 :datum predicate-name
1476 :expected-type
'symbol
1477 :format-control
"The SATISFIES predicate name is not a symbol: ~S"
1478 :format-arguments
(list predicate-name
)))
1479 (case predicate-name
1480 (keywordp (literal-ctype *satisfies-keywordp-type
*))
1481 (legal-fun-name-p (literal-ctype *fun-name-type
*))
1482 (t (%make-hairy-type whole
))))
1486 (!define-type-method
(negation :negate
) (x)
1487 (negation-type-type x
))
1489 (!define-type-method
(negation :unparse
) (x)
1490 (if (type= (negation-type-type x
) (specifier-type 'cons
))
1492 `(not ,(type-specifier (negation-type-type x
)))))
1494 (!define-type-method
(negation :simple-subtypep
) (type1 type2
)
1495 (csubtypep (negation-type-type type2
) (negation-type-type type1
)))
1497 (!define-type-method
(negation :complex-subtypep-arg2
) (type1 type2
)
1498 (let* ((complement-type2 (negation-type-type type2
))
1499 (intersection2 (type-intersection2 type1
1502 ;; FIXME: if uncertain, maybe try arg1?
1503 (type= intersection2
*empty-type
*)
1504 (invoke-complex-subtypep-arg1-method type1 type2
))))
1506 (!define-type-method
(negation :complex-subtypep-arg1
) (type1 type2
)
1507 ;; "Incrementally extended heuristic algorithms tend inexorably toward the
1508 ;; incomprehensible." -- http://www.unlambda.com/~james/lambda/lambda.txt
1510 ;; You may not believe this. I couldn't either. But then I sat down
1511 ;; and drew lots of Venn diagrams. Comments involving a and b refer
1512 ;; to the call (subtypep '(not a) 'b) -- CSR, 2002-02-27.
1514 ;; (Several logical truths in this block are true as long as
1515 ;; b/=T. As of sbcl-0.7.1.28, it seems impossible to construct a
1516 ;; case with b=T where we actually reach this type method, but
1517 ;; we'll test for and exclude this case anyway, since future
1518 ;; maintenance might make it possible for it to end up in this
1520 (multiple-value-bind (equal certain
)
1521 (type= type2
*universal-type
*)
1523 (return (values nil nil
)))
1525 (return (values t t
))))
1526 (let ((complement-type1 (negation-type-type type1
)))
1527 ;; Do the special cases first, in order to give us a chance if
1528 ;; subtype/supertype relationships are hairy.
1529 (multiple-value-bind (equal certain
)
1530 (type= complement-type1 type2
)
1531 ;; If a = b, ~a is not a subtype of b (unless b=T, which was
1534 (return (values nil nil
)))
1536 (return (values nil t
))))
1537 ;; KLUDGE: ANSI requires that the SUBTYPEP result between any
1538 ;; two built-in atomic type specifiers never be uncertain. This
1539 ;; is hard to do cleanly for the built-in types whose
1540 ;; definitions include (NOT FOO), i.e. CONS and RATIO. However,
1541 ;; we can do it with this hack, which uses our global knowledge
1542 ;; that our implementation of the type system uses disjoint
1543 ;; implementation types to represent disjoint sets (except when
1544 ;; types are contained in other types). (This is a KLUDGE
1545 ;; because it's fragile. Various changes in internal
1546 ;; representation in the type system could make it start
1547 ;; confidently returning incorrect results.) -- WHN 2002-03-08
1548 (unless (or (type-might-contain-other-types-p complement-type1
)
1549 (type-might-contain-other-types-p type2
))
1550 ;; Because of the way our types which don't contain other
1551 ;; types are disjoint subsets of the space of possible values,
1552 ;; (SUBTYPEP '(NOT AA) 'B)=NIL when AA and B are simple (and B
1553 ;; is not T, as checked above).
1554 (return (values nil t
)))
1555 ;; The old (TYPE= TYPE1 TYPE2) branch would never be taken, as
1556 ;; TYPE1 and TYPE2 will only be equal if they're both NOT types,
1557 ;; and then the :SIMPLE-SUBTYPEP method would be used instead.
1558 ;; But a CSUBTYPEP relationship might still hold:
1559 (multiple-value-bind (equal certain
)
1560 (csubtypep complement-type1 type2
)
1561 ;; If a is a subtype of b, ~a is not a subtype of b (unless
1562 ;; b=T, which was excluded above).
1564 (return (values nil nil
)))
1566 (return (values nil t
))))
1567 (multiple-value-bind (equal certain
)
1568 (csubtypep type2 complement-type1
)
1569 ;; If b is a subtype of a, ~a is not a subtype of b. (FIXME:
1570 ;; That's not true if a=T. Do we know at this point that a is
1573 (return (values nil nil
)))
1575 (return (values nil t
))))
1576 ;; old CSR comment ca. 0.7.2, now obsoleted by the SIMPLE-CTYPE?
1577 ;; KLUDGE case above: Other cases here would rely on being able
1578 ;; to catch all possible cases, which the fragility of this type
1579 ;; system doesn't inspire me; for instance, if a is type= to ~b,
1580 ;; then we want T, T; if this is not the case and the types are
1581 ;; disjoint (have an intersection of *empty-type*) then we want
1582 ;; NIL, T; else if the union of a and b is the *universal-type*
1583 ;; then we want T, T. So currently we still claim to be unsure
1584 ;; about e.g. (subtypep '(not fixnum) 'single-float).
1586 ;; OTOH we might still get here:
1589 (!define-type-method
(negation :complex-
=) (type1 type2
)
1590 ;; (NOT FOO) isn't equivalent to anything that's not a negation
1591 ;; type, except possibly a type that might contain it in disguise.
1592 (declare (ignore type2
))
1593 (if (type-might-contain-other-types-p type1
)
1597 (!define-type-method
(negation :simple-intersection2
) (type1 type2
)
1598 (let ((not1 (negation-type-type type1
))
1599 (not2 (negation-type-type type2
)))
1601 ((csubtypep not1 not2
) type2
)
1602 ((csubtypep not2 not1
) type1
)
1603 ;; Why no analagous clause to the disjoint in the SIMPLE-UNION2
1604 ;; method, below? The clause would read
1606 ;; ((EQ (TYPE-UNION NOT1 NOT2) *UNIVERSAL-TYPE*) *EMPTY-TYPE*)
1608 ;; but with proper canonicalization of negation types, there's
1609 ;; no way of constructing two negation types with union of their
1610 ;; negations being the universal type.
1612 (aver (not (eq (type-union not1 not2
) *universal-type
*)))
1615 (defun maybe-complex-array-refinement (type1 type2
)
1616 (let* ((ntype (negation-type-type type2
))
1617 (ndims (array-type-dimensions ntype
))
1618 (ncomplexp (array-type-complexp ntype
))
1619 (nseltype (array-type-specialized-element-type ntype
))
1620 (neltype (array-type-element-type ntype
)))
1621 (if (and (eql ndims
'*) (null ncomplexp
)
1622 (eq neltype
*wild-type
*) (eq nseltype
*wild-type
*))
1623 (make-array-type (array-type-dimensions type1
)
1625 :element-type
(array-type-element-type type1
)
1626 :specialized-element-type
(array-type-specialized-element-type type1
)))))
1628 (!define-type-method
(negation :complex-intersection2
) (type1 type2
)
1630 ((csubtypep type1
(negation-type-type type2
)) *empty-type
*)
1631 ((eq (type-intersection type1
(negation-type-type type2
)) *empty-type
*)
1633 ((and (array-type-p type1
) (array-type-p (negation-type-type type2
)))
1634 (maybe-complex-array-refinement type1 type2
))
1637 (!define-type-method
(negation :simple-union2
) (type1 type2
)
1638 (let ((not1 (negation-type-type type1
))
1639 (not2 (negation-type-type type2
)))
1641 ((csubtypep not1 not2
) type1
)
1642 ((csubtypep not2 not1
) type2
)
1643 ((eq (type-intersection not1 not2
) *empty-type
*)
1647 (!define-type-method
(negation :complex-union2
) (type1 type2
)
1649 ((csubtypep (negation-type-type type2
) type1
) *universal-type
*)
1650 ((eq (type-intersection type1
(negation-type-type type2
)) *empty-type
*)
1654 (!define-type-method
(negation :simple-
=) (type1 type2
)
1655 (type= (negation-type-type type1
) (negation-type-type type2
)))
1657 (!def-type-translator not
:list
((:context context
) typespec
)
1658 (type-negation (specifier-type-r context typespec
)))
1662 (declaim (inline numeric-type-equal
))
1663 (defun numeric-type-equal (type1 type2
)
1664 (and (eq (numeric-type-class type1
) (numeric-type-class type2
))
1665 (eq (numeric-type-format type1
) (numeric-type-format type2
))
1666 (eq (numeric-type-complexp type1
) (numeric-type-complexp type2
))))
1668 (!define-type-method
(number :simple-
=) (type1 type2
)
1670 (and (numeric-type-equal type1 type2
)
1671 (equalp (numeric-type-low type1
) (numeric-type-low type2
))
1672 (equalp (numeric-type-high type1
) (numeric-type-high type2
)))
1675 (!define-type-method
(number :negate
) (type)
1676 (if (and (null (numeric-type-low type
)) (null (numeric-type-high type
)))
1677 (make-negation-type type
)
1679 (make-negation-type (modified-numeric-type type
:low nil
:high nil
))
1681 ((null (numeric-type-low type
))
1682 (modified-numeric-type
1684 :low
(let ((h (numeric-type-high type
)))
1685 (if (consp h
) (car h
) (list h
)))
1687 ((null (numeric-type-high type
))
1688 (modified-numeric-type
1691 :high
(let ((l (numeric-type-low type
)))
1692 (if (consp l
) (car l
) (list l
)))))
1694 (modified-numeric-type
1697 :high
(let ((l (numeric-type-low type
)))
1698 (if (consp l
) (car l
) (list l
))))
1699 (modified-numeric-type
1701 :low
(let ((h (numeric-type-high type
)))
1702 (if (consp h
) (car h
) (list h
)))
1705 (!define-type-method
(number :unparse
) (type)
1706 (let* ((complexp (numeric-type-complexp type
))
1707 (low (numeric-type-low type
))
1708 (high (numeric-type-high type
))
1709 (base (case (numeric-type-class type
)
1711 (rational 'rational
)
1712 (float (or (numeric-type-format type
) 'float
))
1715 (cond ((and (eq base
'integer
) high low
)
1716 (let ((high-count (logcount high
))
1717 (high-length (integer-length high
)))
1719 (cond ((= high
0) '(integer 0 0))
1721 ((and (= high-count high-length
)
1722 (plusp high-length
))
1723 `(unsigned-byte ,high-length
))
1725 `(mod ,(1+ high
)))))
1726 ((and (= low sb
!xc
:most-negative-fixnum
)
1727 (= high sb
!xc
:most-positive-fixnum
))
1729 ((and (= low
(lognot high
))
1730 (= high-count high-length
)
1732 `(signed-byte ,(1+ high-length
)))
1734 `(integer ,low
,high
)))))
1735 (high `(,base
,(or low
'*) ,high
))
1737 (if (and (eq base
'integer
) (= low
0))
1745 (aver (neq base
+bounds
'real
))
1746 `(complex ,base
+bounds
))
1748 (aver (eq base
+bounds
'real
))
1751 (!define-type-method
(number :singleton-p
) (type)
1752 (let ((low (numeric-type-low type
))
1753 (high (numeric-type-high type
)))
1756 (eql (numeric-type-complexp type
) :real
)
1757 (member (numeric-type-class type
) '(integer rational
1758 #-sb-xc-host float
)))
1759 (values t
(numeric-type-low type
))
1762 ;;; Return true if X is "less than or equal" to Y, taking open bounds
1763 ;;; into consideration. CLOSED is the predicate used to test the bound
1764 ;;; on a closed interval (e.g. <=), and OPEN is the predicate used on
1765 ;;; open bounds (e.g. <). Y is considered to be the outside bound, in
1766 ;;; the sense that if it is infinite (NIL), then the test succeeds,
1767 ;;; whereas if X is infinite, then the test fails (unless Y is also
1770 ;;; This is for comparing bounds of the same kind, e.g. upper and
1771 ;;; upper. Use NUMERIC-BOUND-TEST* for different kinds of bounds.
1772 (defmacro numeric-bound-test
(x y closed open
)
1777 (,closed
(car ,x
) (car ,y
))
1778 (,closed
(car ,x
) ,y
)))
1784 ;;; This is used to compare upper and lower bounds. This is different
1785 ;;; from the same-bound case:
1786 ;;; -- Since X = NIL is -infinity, whereas y = NIL is +infinity, we
1787 ;;; return true if *either* arg is NIL.
1788 ;;; -- an open inner bound is "greater" and also squeezes the interval,
1789 ;;; causing us to use the OPEN test for those cases as well.
1790 (defmacro numeric-bound-test
* (x y closed open
)
1795 (,open
(car ,x
) (car ,y
))
1796 (,open
(car ,x
) ,y
)))
1802 ;;; Return whichever of the numeric bounds X and Y is "maximal"
1803 ;;; according to the predicates CLOSED (e.g. >=) and OPEN (e.g. >).
1804 ;;; This is only meaningful for maximizing like bounds, i.e. upper and
1805 ;;; upper. If MAX-P is true, then we return NIL if X or Y is NIL,
1806 ;;; otherwise we return the other arg.
1807 (defmacro numeric-bound-max
(x y closed open max-p
)
1810 `(cond ((not ,n-x
) ,(if max-p nil n-y
))
1811 ((not ,n-y
) ,(if max-p nil n-x
))
1814 (if (,closed
(car ,n-x
) (car ,n-y
)) ,n-x
,n-y
)
1815 (if (,open
(car ,n-x
) ,n-y
) ,n-x
,n-y
)))
1818 (if (,open
(car ,n-y
) ,n-x
) ,n-y
,n-x
)
1819 (if (,closed
,n-y
,n-x
) ,n-y
,n-x
))))))
1821 (!define-type-method
(number :simple-subtypep
) (type1 type2
)
1822 (let ((class1 (numeric-type-class type1
))
1823 (class2 (numeric-type-class type2
))
1824 (complexp2 (numeric-type-complexp type2
))
1825 (format2 (numeric-type-format type2
))
1826 (low1 (numeric-type-low type1
))
1827 (high1 (numeric-type-high type1
))
1828 (low2 (numeric-type-low type2
))
1829 (high2 (numeric-type-high type2
)))
1830 ;; If one is complex and the other isn't, they are disjoint.
1831 (cond ((not (or (eq (numeric-type-complexp type1
) complexp2
)
1834 ;; If the classes are specified and different, the types are
1835 ;; disjoint unless type2 is RATIONAL and type1 is INTEGER.
1836 ;; [ or type1 is INTEGER and type2 is of the form (RATIONAL
1837 ;; X X) for integral X, but this is dealt with in the
1838 ;; canonicalization inside MAKE-NUMERIC-TYPE ]
1839 ((not (or (eq class1 class2
)
1841 (and (eq class1
'integer
) (eq class2
'rational
))))
1843 ;; If the float formats are specified and different, the types
1845 ((not (or (eq (numeric-type-format type1
) format2
)
1848 ;; Check the bounds.
1849 ((and (numeric-bound-test low1 low2
>= >)
1850 (numeric-bound-test high1 high2
<= <))
1855 (!define-superclasses number
((number)) !cold-init-forms
)
1857 ;;; If the high bound of LOW is adjacent to the low bound of HIGH,
1858 ;;; then return true, otherwise NIL.
1859 (defun numeric-types-adjacent (low high
)
1860 (let ((low-bound (numeric-type-high low
))
1861 (high-bound (numeric-type-low high
)))
1862 (cond ((not (and low-bound high-bound
)) nil
)
1863 ((and (consp low-bound
) (consp high-bound
)) nil
)
1865 (let ((low-value (car low-bound
)))
1866 (or (eql low-value high-bound
)
1868 (load-time-value (make-unportable-float
1869 :single-float-negative-zero
) t
))
1870 (eql high-bound
0f0
))
1871 (and (eql low-value
0f0
)
1873 (load-time-value (make-unportable-float
1874 :single-float-negative-zero
) t
)))
1876 (load-time-value (make-unportable-float
1877 :double-float-negative-zero
) t
))
1878 (eql high-bound
0d0
))
1879 (and (eql low-value
0d0
)
1881 (load-time-value (make-unportable-float
1882 :double-float-negative-zero
) t
))))))
1884 (let ((high-value (car high-bound
)))
1885 (or (eql high-value low-bound
)
1886 (and (eql high-value
1887 (load-time-value (make-unportable-float
1888 :single-float-negative-zero
) t
))
1889 (eql low-bound
0f0
))
1890 (and (eql high-value
0f0
)
1892 (load-time-value (make-unportable-float
1893 :single-float-negative-zero
) t
)))
1894 (and (eql high-value
1895 (load-time-value (make-unportable-float
1896 :double-float-negative-zero
) t
))
1897 (eql low-bound
0d0
))
1898 (and (eql high-value
0d0
)
1900 (load-time-value (make-unportable-float
1901 :double-float-negative-zero
) t
))))))
1902 ((and (eq (numeric-type-class low
) 'integer
)
1903 (eq (numeric-type-class high
) 'integer
))
1904 (eql (1+ low-bound
) high-bound
))
1908 ;;; Return a numeric type that is a supertype for both TYPE1 and TYPE2.
1910 ;;; Binding *APPROXIMATE-NUMERIC-UNIONS* to T allows merging non-adjacent
1911 ;;; numeric types, eg (OR (INTEGER 0 12) (INTEGER 20 128)) => (INTEGER 0 128),
1912 ;;; the compiler does this occasionally during type-derivation to avoid
1913 ;;; creating absurdly complex unions of numeric types.
1914 (defvar *approximate-numeric-unions
* nil
)
1916 (!define-type-method
(number :simple-union2
) (type1 type2
)
1917 (declare (type numeric-type type1 type2
))
1918 (cond ((csubtypep type1 type2
) type2
)
1919 ((csubtypep type2 type1
) type1
)
1921 (let ((class1 (numeric-type-class type1
))
1922 (format1 (numeric-type-format type1
))
1923 (complexp1 (numeric-type-complexp type1
))
1924 (class2 (numeric-type-class type2
))
1925 (format2 (numeric-type-format type2
))
1926 (complexp2 (numeric-type-complexp type2
)))
1928 ((and (eq class1 class2
)
1929 (eq format1 format2
)
1930 (eq complexp1 complexp2
)
1931 (or *approximate-numeric-unions
*
1932 (numeric-types-intersect type1 type2
)
1933 (numeric-types-adjacent type1 type2
)
1934 (numeric-types-adjacent type2 type1
)))
1939 :low
(numeric-bound-max (numeric-type-low type1
)
1940 (numeric-type-low type2
)
1942 :high
(numeric-bound-max (numeric-type-high type1
)
1943 (numeric-type-high type2
)
1945 ;; FIXME: These two clauses are almost identical, and the
1946 ;; consequents are in fact identical in every respect.
1947 ((and (eq class1
'rational
)
1948 (eq class2
'integer
)
1949 (eq format1 format2
)
1950 (eq complexp1 complexp2
)
1951 (integerp (numeric-type-low type2
))
1952 (integerp (numeric-type-high type2
))
1953 (= (numeric-type-low type2
) (numeric-type-high type2
))
1954 (or *approximate-numeric-unions
*
1955 (numeric-types-adjacent type1 type2
)
1956 (numeric-types-adjacent type2 type1
)))
1961 :low
(numeric-bound-max (numeric-type-low type1
)
1962 (numeric-type-low type2
)
1964 :high
(numeric-bound-max (numeric-type-high type1
)
1965 (numeric-type-high type2
)
1967 ((and (eq class1
'integer
)
1968 (eq class2
'rational
)
1969 (eq format1 format2
)
1970 (eq complexp1 complexp2
)
1971 (integerp (numeric-type-low type1
))
1972 (integerp (numeric-type-high type1
))
1973 (= (numeric-type-low type1
) (numeric-type-high type1
))
1974 (or *approximate-numeric-unions
*
1975 (numeric-types-adjacent type1 type2
)
1976 (numeric-types-adjacent type2 type1
)))
1981 :low
(numeric-bound-max (numeric-type-low type1
)
1982 (numeric-type-low type2
)
1984 :high
(numeric-bound-max (numeric-type-high type1
)
1985 (numeric-type-high type2
)
1990 (!cold-init-forms
;; is !PRECOMPUTE-TYPES not doing the right thing?
1991 (setf (info :type
:kind
'number
) :primitive
)
1992 (setf (info :type
:builtin
'number
)
1993 (make-numeric-type :complexp nil
)))
1995 (!def-type-translator complex
((:context context
) &optional
(typespec '*))
1996 (if (eq typespec
'*)
1997 (specifier-type '(complex real
))
1998 (labels ((not-numeric ()
1999 (error "The component type for COMPLEX is not numeric: ~S"
2002 (error "The component type for COMPLEX is not a subtype of REAL: ~S"
2004 (complex1 (component-type)
2005 (unless (numeric-type-p component-type
)
2007 (when (eq (numeric-type-complexp component-type
) :complex
)
2009 (if (csubtypep component-type
(specifier-type '(eql 0)))
2011 (modified-numeric-type component-type
2012 :complexp
:complex
)))
2015 ((eq ctype
*empty-type
*) *empty-type
*)
2016 ((eq ctype
*universal-type
*) (not-real))
2017 ((typep ctype
'numeric-type
) (complex1 ctype
))
2018 ((typep ctype
'union-type
)
2020 (mapcar #'do-complex
(union-type-types ctype
))))
2021 ((typep ctype
'member-type
)
2023 (mapcar-member-type-members
2024 (lambda (x) (do-complex (ctype-of x
)))
2026 ((and (typep ctype
'intersection-type
)
2027 ;; FIXME: This is very much a
2028 ;; not-quite-worst-effort, but we are required to do
2029 ;; something here because of our representation of
2030 ;; RATIO as (AND RATIONAL (NOT INTEGER)): we must
2031 ;; allow users to ask about (COMPLEX RATIO). This
2032 ;; will of course fail to work right on such types
2033 ;; as (AND INTEGER (SATISFIES ZEROP))...
2034 (let ((numbers (remove-if-not
2036 (intersection-type-types ctype
))))
2038 (null (cdr numbers
))
2039 (eq (numeric-type-complexp (car numbers
)) :real
)
2040 (complex1 (car numbers
))))))
2042 (multiple-value-bind (subtypep certainly
)
2043 (csubtypep ctype
(specifier-type 'real
))
2044 (if (and (not subtypep
) certainly
)
2046 ;; ANSI just says that TYPESPEC is any subtype of
2047 ;; type REAL, not necessarily a NUMERIC-TYPE. In
2048 ;; particular, at this point TYPESPEC could legally
2049 ;; be a hairy type like (AND NUMBER (SATISFIES
2050 ;; REALP) (SATISFIES ZEROP)), in which case we fall
2051 ;; through the logic above and end up here,
2053 ;; FIXME: (COMPLEX NUMBER) is not rejected but should
2054 ;; be, as NUMBER is clearly not a subtype of real.
2055 (bug "~@<(known bug #145): The type ~S is too hairy to be ~
2056 used for a COMPLEX component.~:@>"
2058 (let ((ctype (specifier-type-r context typespec
)))
2059 (do-complex ctype
)))))
2061 ;;; If X is *, return NIL, otherwise return the bound, which must be a
2062 ;;; member of TYPE or a one-element list of a member of TYPE.
2063 ;;; This is not necessarily the canonical bound. An integer bound
2064 ;;; should always be an atom, which we'll enforce later if needed.
2065 #!-sb-fluid
(declaim (inline valid-bound
))
2066 (defun valid-bound (bound type
)
2067 (cond ((eq bound
'*) nil
)
2068 ((sb!xc
:typep
(if (singleton-p bound
) (car bound
) bound
) type
) bound
)
2070 (error "Bound is not * or ~A ~S or list of one ~:*~S: ~S"
2071 (if (eq type
'integer
) "an" "a") type bound
))))
2073 (!def-type-translator integer
(&optional
(low '*) (high '*))
2074 (let ((lb (valid-bound low
'integer
))
2075 (hb (valid-bound high
'integer
)))
2076 (make-numeric-type :class
'integer
:complexp
:real
2077 :enumerable
(not (null (and lb hb
)))
2080 (defmacro !def-bounded-type
(type class format
)
2081 `(!def-type-translator
,type
(&optional
(low '*) (high '*))
2082 (let ((lb (valid-bound low
',type
))
2083 (hb (valid-bound high
',type
)))
2084 (make-numeric-type :class
',class
:format
',format
2085 :low lb
:high hb
))))
2087 (!def-bounded-type rational rational nil
)
2089 ;;; Unlike CMU CL, we represent the types FLOAT and REAL as
2090 ;;; UNION-TYPEs of more primitive types, in order to make
2091 ;;; type representation more unique, avoiding problems in the
2092 ;;; simplification of things like
2093 ;;; (subtypep '(or (single-float -1.0 1.0) (single-float 0.1))
2094 ;;; '(or (real -1 7) (single-float 0.1) (single-float -1.0 1.0)))
2095 ;;; When we allowed REAL to remain as a separate NUMERIC-TYPE,
2096 ;;; it was too easy for the first argument to be simplified to
2097 ;;; '(SINGLE-FLOAT -1.0), and for the second argument to be simplified
2098 ;;; to '(OR (REAL -1 7) (SINGLE-FLOAT 0.1)) and then for the
2099 ;;; SUBTYPEP to fail (returning NIL,T instead of T,T) because
2100 ;;; the first argument can't be seen to be a subtype of any of the
2101 ;;; terms in the second argument.
2103 ;;; The old CMU CL way was:
2104 ;;; (!def-bounded-type float float nil)
2105 ;;; (!def-bounded-type real nil nil)
2107 ;;; FIXME: If this new way works for a while with no weird new
2108 ;;; problems, we can go back and rip out support for separate FLOAT
2109 ;;; and REAL flavors of NUMERIC-TYPE. The new way was added in
2110 ;;; sbcl-0.6.11.22, 2001-03-21.
2112 ;;; FIXME: It's probably necessary to do something to fix the
2113 ;;; analogous problem with INTEGER and RATIONAL types. Perhaps
2114 ;;; bounded RATIONAL types should be represented as (OR RATIO INTEGER).
2115 (defun coerce-bound (bound type upperp inner-coerce-bound-fun
)
2116 (declare (type function inner-coerce-bound-fun
))
2119 (funcall inner-coerce-bound-fun bound type upperp
)))
2121 (macrolet ((fp-const (name)
2122 `(load-time-value (locally (declare (notinline symbol-value
))
2123 (symbol-value ',name
)) t
)))
2124 (defun inner-coerce-real-bound (bound type upperp
)
2125 #+sb-xc-host
(declare (ignore upperp
))
2126 (let #+sb-xc-host
()
2127 #-sb-xc-host
((nl (fp-const sb
!xc
:most-negative-long-float
))
2128 (pl (fp-const sb
!xc
:most-positive-long-float
)))
2129 (let ((nbound (if (consp bound
) (car bound
) bound
))
2130 (consp (consp bound
)))
2134 (list (rational nbound
))
2138 ((floatp nbound
) bound
)
2140 ;; Coerce to the widest float format available, to avoid
2141 ;; unnecessary loss of precision, but don't coerce
2142 ;; unrepresentable numbers, except on the host where we
2143 ;; shouldn't be making these types (but KLUDGE: can't even
2144 ;; assert portably that we're not).
2148 (when (< nbound nl
) (return-from inner-coerce-real-bound nl
)))
2150 (when (> nbound pl
) (return-from inner-coerce-real-bound pl
))))
2151 (let ((result (coerce nbound
'long-float
)))
2152 (if consp
(list result
) result
)))))))))
2153 (defun inner-coerce-float-bound (bound type upperp
)
2154 #+sb-xc-host
(declare (ignore upperp
))
2155 (let #+sb-xc-host
()
2156 #-sb-xc-host
((nd (fp-const sb
!xc
:most-negative-double-float
))
2157 (pd (fp-const sb
!xc
:most-positive-double-float
))
2158 (ns (fp-const sb
!xc
:most-negative-single-float
))
2159 (ps (fp-const sb
!xc
:most-positive-single-float
)))
2160 (let ((nbound (if (consp bound
) (car bound
) bound
))
2161 (consp (consp bound
)))
2165 ((typep nbound
'single-float
) bound
)
2170 (when (< nbound ns
) (return-from inner-coerce-float-bound ns
)))
2172 (when (> nbound ps
) (return-from inner-coerce-float-bound ps
))))
2173 (let ((result (coerce nbound
'single-float
)))
2174 (if consp
(list result
) result
)))))
2177 ((typep nbound
'double-float
) bound
)
2182 (when (< nbound nd
) (return-from inner-coerce-float-bound nd
)))
2184 (when (> nbound pd
) (return-from inner-coerce-float-bound pd
))))
2185 (let ((result (coerce nbound
'double-float
)))
2186 (if consp
(list result
) result
)))))))))
2188 (defun coerced-real-bound (bound type upperp
)
2189 (coerce-bound bound type upperp
#'inner-coerce-real-bound
))
2190 (defun coerced-float-bound (bound type upperp
)
2191 (coerce-bound bound type upperp
#'inner-coerce-float-bound
))
2192 (!def-type-translator real
(&optional
(low '*) (high '*))
2193 (specifier-type `(or (float ,(coerced-real-bound low
'float nil
)
2194 ,(coerced-real-bound high
'float t
))
2195 (rational ,(coerced-real-bound low
'rational nil
)
2196 ,(coerced-real-bound high
'rational t
)))))
2197 (!def-type-translator float
(&optional
(low '*) (high '*))
2199 `(or (single-float ,(coerced-float-bound low
'single-float nil
)
2200 ,(coerced-float-bound high
'single-float t
))
2201 (double-float ,(coerced-float-bound low
'double-float nil
)
2202 ,(coerced-float-bound high
'double-float t
))
2203 #!+long-float
,(error "stub: no long float support yet"))))
2205 (macrolet ((define-float-format (f) `(!def-bounded-type
,f float
,f
)))
2206 (define-float-format single-float
)
2207 (define-float-format double-float
))
2209 (defun numeric-types-intersect (type1 type2
)
2210 (declare (type numeric-type type1 type2
))
2211 (let* ((class1 (numeric-type-class type1
))
2212 (class2 (numeric-type-class type2
))
2213 (complexp1 (numeric-type-complexp type1
))
2214 (complexp2 (numeric-type-complexp type2
))
2215 (format1 (numeric-type-format type1
))
2216 (format2 (numeric-type-format type2
))
2217 (low1 (numeric-type-low type1
))
2218 (high1 (numeric-type-high type1
))
2219 (low2 (numeric-type-low type2
))
2220 (high2 (numeric-type-high type2
)))
2221 ;; If one is complex and the other isn't, then they are disjoint.
2222 (cond ((not (or (eq complexp1 complexp2
)
2223 (null complexp1
) (null complexp2
)))
2225 ;; If either type is a float, then the other must either be
2226 ;; specified to be a float or unspecified. Otherwise, they
2228 ((and (eq class1
'float
)
2229 (not (member class2
'(float nil
)))) nil
)
2230 ((and (eq class2
'float
)
2231 (not (member class1
'(float nil
)))) nil
)
2232 ;; If the float formats are specified and different, the
2233 ;; types are disjoint.
2234 ((not (or (eq format1 format2
) (null format1
) (null format2
)))
2237 ;; Check the bounds. This is a bit odd because we must
2238 ;; always have the outer bound of the interval as the
2240 (if (numeric-bound-test high1 high2
<= <)
2241 (or (and (numeric-bound-test low1 low2
>= >)
2242 (numeric-bound-test* low1 high2
<= <))
2243 (and (numeric-bound-test low2 low1
>= >)
2244 (numeric-bound-test* low2 high1
<= <)))
2245 (or (and (numeric-bound-test* low2 high1
<= <)
2246 (numeric-bound-test low2 low1
>= >))
2247 (and (numeric-bound-test high2 high1
<= <)
2248 (numeric-bound-test* high2 low1
>= >))))))))
2250 ;;; Take the numeric bound X and convert it into something that can be
2251 ;;; used as a bound in a numeric type with the specified CLASS and
2252 ;;; FORMAT. If UP-P is true, then we round up as needed, otherwise we
2253 ;;; round down. UP-P true implies that X is a lower bound, i.e. (N) > N.
2255 ;;; This is used by NUMERIC-TYPE-INTERSECTION to mash the bound into
2256 ;;; the appropriate type number. X may only be a float when CLASS is
2259 ;;; ### Note: it is possible for the coercion to a float to overflow
2260 ;;; or underflow. This happens when the bound doesn't fit in the
2261 ;;; specified format. In this case, we should really return the
2262 ;;; appropriate {Most | Least}-{Positive | Negative}-XXX-Float float
2263 ;;; of desired format. But these conditions aren't currently signalled
2264 ;;; in any useful way.
2266 ;;; Also, when converting an open rational bound into a float we
2267 ;;; should probably convert it to a closed bound of the closest float
2268 ;;; in the specified format. KLUDGE: In general, open float bounds are
2269 ;;; screwed up. -- (comment from original CMU CL)
2270 (defun round-numeric-bound (x class format up-p
)
2272 (let ((cx (if (consp x
) (car x
) x
)))
2276 (if (and (consp x
) (integerp cx
))
2277 (if up-p
(1+ cx
) (1- cx
))
2278 (if up-p
(ceiling cx
) (floor cx
))))
2282 ((and format
(subtypep format
'double-float
))
2283 (if (<= most-negative-double-float cx most-positive-double-float
)
2287 (if (<= most-negative-single-float cx most-positive-single-float
)
2289 (coerce cx
(or format
'single-float
))
2291 (if (consp x
) (list res
) res
)))))
2294 ;;; Handle the case of type intersection on two numeric types. We use
2295 ;;; TYPES-EQUAL-OR-INTERSECT to throw out the case of types with no
2296 ;;; intersection. If an attribute in TYPE1 is unspecified, then we use
2297 ;;; TYPE2's attribute, which must be at least as restrictive. If the
2298 ;;; types intersect, then the only attributes that can be specified
2299 ;;; and different are the class and the bounds.
2301 ;;; When the class differs, we use the more restrictive class. The
2302 ;;; only interesting case is RATIONAL/INTEGER, since RATIONAL includes
2305 ;;; We make the result lower (upper) bound the maximum (minimum) of
2306 ;;; the argument lower (upper) bounds. We convert the bounds into the
2307 ;;; appropriate numeric type before maximizing. This avoids possible
2308 ;;; confusion due to mixed-type comparisons (but I think the result is
2310 (!define-type-method
(number :simple-intersection2
) (type1 type2
)
2311 (declare (type numeric-type type1 type2
))
2312 (if (numeric-types-intersect type1 type2
)
2313 (let* ((class1 (numeric-type-class type1
))
2314 (class2 (numeric-type-class type2
))
2315 (class (ecase class1
2317 ((integer float
) class1
)
2318 (rational (if (eq class2
'integer
)
2321 (format (or (numeric-type-format type1
)
2322 (numeric-type-format type2
))))
2326 :complexp
(or (numeric-type-complexp type1
)
2327 (numeric-type-complexp type2
))
2328 :low
(numeric-bound-max
2329 (round-numeric-bound (numeric-type-low type1
)
2331 (round-numeric-bound (numeric-type-low type2
)
2334 :high
(numeric-bound-max
2335 (round-numeric-bound (numeric-type-high type1
)
2337 (round-numeric-bound (numeric-type-high type2
)
2342 ;;; Given two float formats, return the one with more precision. If
2343 ;;; either one is null, return NIL.
2344 (defun float-format-max (f1 f2
)
2346 (dolist (f *float-formats
* (error "bad float format: ~S" f1
))
2347 (when (or (eq f f1
) (eq f f2
))
2350 ;;; Return the result of an operation on TYPE1 and TYPE2 according to
2351 ;;; the rules of numeric contagion. This is always NUMBER, some float
2352 ;;; format (possibly complex) or RATIONAL. Due to rational
2353 ;;; canonicalization, there isn't much we can do here with integers or
2354 ;;; rational complex numbers.
2356 ;;; If either argument is not a NUMERIC-TYPE, then return NUMBER. This
2357 ;;; is useful mainly for allowing types that are technically numbers,
2358 ;;; but not a NUMERIC-TYPE.
2359 (defun numeric-contagion (type1 type2
)
2360 (if (and (numeric-type-p type1
) (numeric-type-p type2
))
2361 (let ((class1 (numeric-type-class type1
))
2362 (class2 (numeric-type-class type2
))
2363 (format1 (numeric-type-format type1
))
2364 (format2 (numeric-type-format type2
))
2365 (complexp1 (numeric-type-complexp type1
))
2366 (complexp2 (numeric-type-complexp type2
)))
2367 (cond ((or (null complexp1
)
2369 (specifier-type 'number
))
2373 :format
(ecase class2
2374 (float (float-format-max format1 format2
))
2375 ((integer rational
) format1
)
2377 ;; A double-float with any real number is a
2380 (if (eq format1
'double-float
)
2383 ;; A long-float with any real number is a
2386 (if (eq format1
'long-float
)
2389 :complexp
(if (or (eq complexp1
:complex
)
2390 (eq complexp2
:complex
))
2393 ((eq class2
'float
) (numeric-contagion type2 type1
))
2394 ((and (eq complexp1
:real
) (eq complexp2
:real
))
2396 :class
(and class1 class2
'rational
)
2399 (specifier-type 'number
))))
2400 (specifier-type 'number
)))
2404 (!define-type-method
(array :simple-
=) (type1 type2
)
2405 (cond ((not (and (equal (array-type-dimensions type1
)
2406 (array-type-dimensions type2
))
2407 (eq (array-type-complexp type1
)
2408 (array-type-complexp type2
))))
2410 ((or (unknown-type-p (array-type-element-type type1
))
2411 (unknown-type-p (array-type-element-type type2
)))
2412 (type= (array-type-element-type type1
)
2413 (array-type-element-type type2
)))
2415 (values (type= (array-type-specialized-element-type type1
)
2416 (array-type-specialized-element-type type2
))
2419 (!define-type-method
(array :negate
) (type)
2420 ;; FIXME (and hint to PFD): we're vulnerable here to attacks of the
2421 ;; form "are (AND ARRAY (NOT (ARRAY T))) and (OR (ARRAY BIT) (ARRAY
2422 ;; NIL) (ARRAY CHAR) ...) equivalent?" -- CSR, 2003-12-10
2423 ;; A symptom of the aforementioned is that the following are not TYPE=
2424 ;; (AND (VECTOR T) (NOT SIMPLE-ARRAY)) ; an ARRAY-TYPE
2425 ;; (AND (VECTOR T) (NOT SIMPLE-VECTOR)) ; an INTERSECTION-TYPE
2426 ;; even though (VECTOR T) makes it so that the (NOT) clause in each can
2427 ;; only provide one additional bit of information: that the vector
2428 ;; is complex as opposed to simple. The rank and element-type are fixed.
2429 (if (and (eq (array-type-dimensions type
) '*)
2430 (eq (array-type-complexp type
) 't
)
2431 (eq (array-type-element-type type
) *wild-type
*))
2432 ;; (NOT <hairy-array>) = either SIMPLE-ARRAY or (NOT ARRAY).
2433 ;; This is deliberately asymmetric - trying to say that NOT simple-array
2434 ;; equals hairy-array leads to infinite recursion.
2435 (type-union (make-array-type '* :complexp nil
2436 :element-type
*wild-type
*)
2438 (make-array-type '* :element-type
*wild-type
*)))
2439 (make-negation-type type
)))
2441 (!define-type-method
(array :unparse
) (type)
2442 (let* ((dims (array-type-dimensions type
))
2443 ;; Compare the specialised element type and the
2444 ;; derived element type. If the derived type
2445 ;; is so small that it jumps to a smaller upgraded
2446 ;; element type, use the specialised element type.
2448 ;; This protects from unparsing
2449 ;; (and (vector (or bit symbol))
2450 ;; (vector (or bit character)))
2451 ;; i.e., the intersection of two T array types,
2453 (stype (array-type-specialized-element-type type
))
2454 (dtype (array-type-element-type type
))
2455 (utype (%upgraded-array-element-type dtype
))
2456 (eltype (type-specifier (if (type= stype utype
)
2459 (complexp (array-type-complexp type
)))
2460 (if (and (eq complexp t
) (not *unparse-allow-negation
*))
2461 (setq complexp
:maybe
))
2465 ((t) '(and array
(not simple-array
)))
2467 ((nil) 'simple-array
))
2469 ((t) `(and (array ,eltype
) (not simple-array
)))
2470 ((:maybe
) `(array ,eltype
))
2471 ((nil) `(simple-array ,eltype
)))))
2472 ((= (length dims
) 1)
2475 (if (eq (car dims
) '*)
2478 ((base-char #!-sb-unicode character
) 'base-string
)
2480 (t `(vector ,eltype
)))
2482 (bit `(bit-vector ,(car dims
)))
2483 ((base-char #!-sb-unicode character
)
2484 `(base-string ,(car dims
)))
2485 (t `(vector ,eltype
,(car dims
)))))))
2486 (if (eql complexp
:maybe
)
2488 `(and ,answer
(not simple-array
))))
2489 (if (eq (car dims
) '*)
2491 (bit 'simple-bit-vector
)
2492 ((base-char #!-sb-unicode character
) 'simple-base-string
)
2493 ((t) 'simple-vector
)
2494 (t `(simple-array ,eltype
(*))))
2496 (bit `(simple-bit-vector ,(car dims
)))
2497 ((base-char #!-sb-unicode character
)
2498 `(simple-base-string ,(car dims
)))
2499 ((t) `(simple-vector ,(car dims
)))
2500 (t `(simple-array ,eltype
,dims
))))))
2503 ((t) `(and (array ,eltype
,dims
) (not simple-array
)))
2504 ((:maybe
) `(array ,eltype
,dims
))
2505 ((nil) `(simple-array ,eltype
,dims
)))))))
2507 (!define-type-method
(array :simple-subtypep
) (type1 type2
)
2508 (let ((dims1 (array-type-dimensions type1
))
2509 (dims2 (array-type-dimensions type2
))
2510 (complexp2 (array-type-complexp type2
)))
2511 (cond (;; not subtypep unless dimensions are compatible
2512 (not (or (eq dims2
'*)
2513 (and (not (eq dims1
'*))
2514 ;; (sbcl-0.6.4 has trouble figuring out that
2515 ;; DIMS1 and DIMS2 must be lists at this
2516 ;; point, and knowing that is important to
2517 ;; compiling EVERY efficiently.)
2518 (= (length (the list dims1
))
2519 (length (the list dims2
)))
2520 (every (lambda (x y
)
2521 (or (eq y
'*) (eql x y
)))
2523 (the list dims2
)))))
2525 ;; not subtypep unless complexness is compatible
2526 ((not (or (eq complexp2
:maybe
)
2527 (eq (array-type-complexp type1
) complexp2
)))
2529 ;; Since we didn't fail any of the tests above, we win
2530 ;; if the TYPE2 element type is wild.
2531 ((eq (array-type-element-type type2
) *wild-type
*)
2533 (;; Since we didn't match any of the special cases above, if
2534 ;; either element type is unknown we can only give a good
2535 ;; answer if they are the same.
2536 (or (unknown-type-p (array-type-element-type type1
))
2537 (unknown-type-p (array-type-element-type type2
)))
2538 (if (type= (array-type-element-type type1
)
2539 (array-type-element-type type2
))
2542 (;; Otherwise, the subtype relationship holds iff the
2543 ;; types are equal, and they're equal iff the specialized
2544 ;; element types are identical.
2546 (values (type= (array-type-specialized-element-type type1
)
2547 (array-type-specialized-element-type type2
))
2550 (!define-superclasses array
((vector vector
) (array)) !cold-init-forms
)
2552 (defun array-types-intersect (type1 type2
)
2553 (declare (type array-type type1 type2
))
2554 (let ((dims1 (array-type-dimensions type1
))
2555 (dims2 (array-type-dimensions type2
))
2556 (complexp1 (array-type-complexp type1
))
2557 (complexp2 (array-type-complexp type2
)))
2558 ;; See whether dimensions are compatible.
2559 (cond ((not (or (eq dims1
'*) (eq dims2
'*)
2560 (and (= (length dims1
) (length dims2
))
2561 (every (lambda (x y
)
2562 (or (eq x
'*) (eq y
'*) (= x y
)))
2565 ;; See whether complexpness is compatible.
2566 ((not (or (eq complexp1
:maybe
)
2567 (eq complexp2
:maybe
)
2568 (eq complexp1 complexp2
)))
2572 ;; If either element type is wild, then they intersect.
2573 ;; Otherwise, the types must be identical.
2575 ;; FIXME: There seems to have been a fair amount of
2576 ;; confusion about the distinction between requested element
2577 ;; type and specialized element type; here is one of
2578 ;; them. If we request an array to hold objects of an
2579 ;; unknown type, we can do no better than represent that
2580 ;; type as an array specialized on wild-type. We keep the
2581 ;; requested element-type in the -ELEMENT-TYPE slot, and
2582 ;; *WILD-TYPE* in the -SPECIALIZED-ELEMENT-TYPE. So, here,
2583 ;; we must test for the SPECIALIZED slot being *WILD-TYPE*,
2584 ;; not just the ELEMENT-TYPE slot. Maybe the return value
2585 ;; in that specific case should be T, NIL? Or maybe this
2586 ;; function should really be called
2587 ;; ARRAY-TYPES-COULD-POSSIBLY-INTERSECT? In any case, this
2588 ;; was responsible for bug #123, and this whole issue could
2589 ;; do with a rethink and/or a rewrite. -- CSR, 2002-08-21
2590 ((or (eq (array-type-specialized-element-type type1
) *wild-type
*)
2591 (eq (array-type-specialized-element-type type2
) *wild-type
*)
2592 (type= (array-type-specialized-element-type type1
)
2593 (array-type-specialized-element-type type2
)))
2599 (defun unite-array-types-complexp (type1 type2
)
2600 (let ((complexp1 (array-type-complexp type1
))
2601 (complexp2 (array-type-complexp type2
)))
2603 ((eq complexp1 complexp2
)
2604 ;; both types are the same complexp-ity
2605 (values complexp1 t
))
2606 ((eq complexp1
:maybe
)
2607 ;; type1 is wild-complexp
2608 (values :maybe type1
))
2609 ((eq complexp2
:maybe
)
2610 ;; type2 is wild-complexp
2611 (values :maybe type2
))
2613 ;; both types partition the complexp-space
2614 (values :maybe nil
)))))
2616 (defun unite-array-types-dimensions (type1 type2
)
2617 (let ((dims1 (array-type-dimensions type1
))
2618 (dims2 (array-type-dimensions type2
)))
2619 (cond ((equal dims1 dims2
)
2620 ;; both types are same dimensionality
2623 ;; type1 is wild-dimensions
2626 ;; type2 is wild-dimensions
2628 ((not (= (length dims1
) (length dims2
)))
2629 ;; types have different number of dimensions
2630 (values :incompatible nil
))
2632 ;; we need to check on a per-dimension basis
2633 (let* ((supertype1 t
)
2636 (result (mapcar (lambda (dim1 dim2
)
2641 (setf supertype2 nil
)
2644 (setf supertype1 nil
)
2647 (setf compatible nil
))))
2650 ((or (not compatible
)
2651 (and (not supertype1
)
2653 (values :incompatible nil
))
2654 ((and supertype1 supertype2
)
2655 (values result supertype1
))
2657 (values result
(if supertype1 type1 type2
)))))))))
2659 (defun unite-array-types-element-types (type1 type2
)
2660 ;; FIXME: We'd love to be able to unite the full set of specialized
2661 ;; array element types up to *wild-type*, but :simple-union2 is
2662 ;; performed pairwise, so we don't have a good hook for it and our
2663 ;; representation doesn't allow us to easily detect the situation
2665 ;; But see SIMPLIFY-ARRAY-UNIONS which is able to do something like that.
2666 (let* ((eltype1 (array-type-element-type type1
))
2667 (eltype2 (array-type-element-type type2
))
2668 (stype1 (array-type-specialized-element-type type1
))
2669 (stype2 (array-type-specialized-element-type type2
))
2670 (wild1 (eq eltype1
*wild-type
*))
2671 (wild2 (eq eltype2
*wild-type
*)))
2673 ((type= eltype1 eltype2
)
2674 (values eltype1 stype1 t
))
2676 (values eltype1 stype1 type1
))
2678 (values eltype2 stype2 type2
))
2679 ((not (type= stype1 stype2
))
2680 ;; non-wild types that don't share UAET don't unite
2681 (values :incompatible nil nil
))
2682 ((csubtypep eltype1 eltype2
)
2683 (values eltype2 stype2 type2
))
2684 ((csubtypep eltype2 eltype1
)
2685 (values eltype1 stype1 type1
))
2687 (values :incompatible nil nil
)))))
2689 (defun unite-array-types-supertypes-compatible-p (&rest supertypes
)
2690 ;; supertypes are compatible if they are all T, if there is a single
2691 ;; NIL and all the rest are T, or if all non-T supertypes are the
2692 ;; same and not NIL.
2693 (let ((interesting-supertypes
2694 (remove t supertypes
)))
2695 (or (not interesting-supertypes
)
2696 (equal interesting-supertypes
'(nil))
2697 ;; supertypes are (OR BOOLEAN ARRAY-TYPE), so...
2698 (typep (remove-duplicates interesting-supertypes
)
2699 '(cons array-type null
)))))
2701 (!define-type-method
(array :simple-union2
) (type1 type2
)
2702 (multiple-value-bind
2703 (result-eltype result-stype eltype-supertype
)
2704 (unite-array-types-element-types type1 type2
)
2705 (multiple-value-bind
2706 (result-complexp complexp-supertype
)
2707 (unite-array-types-complexp type1 type2
)
2708 (multiple-value-bind
2709 (result-dimensions dimensions-supertype
)
2710 (unite-array-types-dimensions type1 type2
)
2711 (when (and (not (eq result-dimensions
:incompatible
))
2712 (not (eq result-eltype
:incompatible
))
2713 (unite-array-types-supertypes-compatible-p
2714 eltype-supertype complexp-supertype dimensions-supertype
))
2715 (make-array-type result-dimensions
2716 :complexp result-complexp
2717 :element-type result-eltype
2718 :specialized-element-type result-stype
))))))
2720 (!define-type-method
(array :simple-intersection2
) (type1 type2
)
2721 (declare (type array-type type1 type2
))
2722 (if (array-types-intersect type1 type2
)
2723 (let ((dims1 (array-type-dimensions type1
))
2724 (dims2 (array-type-dimensions type2
))
2725 (complexp1 (array-type-complexp type1
))
2726 (complexp2 (array-type-complexp type2
))
2727 (eltype1 (array-type-element-type type1
))
2728 (eltype2 (array-type-element-type type2
))
2729 (stype1 (array-type-specialized-element-type type1
))
2730 (stype2 (array-type-specialized-element-type type2
)))
2731 (make-array-type (cond ((eq dims1
'*) dims2
)
2732 ((eq dims2
'*) dims1
)
2734 (mapcar (lambda (x y
) (if (eq x
'*) y x
))
2736 :complexp
(if (eq complexp1
:maybe
) complexp2 complexp1
)
2738 ((eq eltype1
*wild-type
*) eltype2
)
2739 ((eq eltype2
*wild-type
*) eltype1
)
2740 (t (type-intersection eltype1 eltype2
)))
2741 :specialized-element-type
(cond
2742 ((eq stype1
*wild-type
*) stype2
)
2743 ((eq stype2
*wild-type
*) stype1
)
2745 (aver (type= stype1 stype2
))
2749 ;;; Check a supplied dimension list to determine whether it is legal,
2750 ;;; and return it in canonical form (as either '* or a list).
2751 (defun canonical-array-dimensions (dims)
2756 (error "Arrays can't have a negative number of dimensions: ~S" dims
))
2757 (when (>= dims sb
!xc
:array-rank-limit
)
2758 (error "array type with too many dimensions: ~S" dims
))
2759 (make-list dims
:initial-element
'*))
2761 (when (>= (length dims
) sb
!xc
:array-rank-limit
)
2762 (error "array type with too many dimensions: ~S" dims
))
2765 (unless (and (integerp dim
)
2767 (< dim sb
!xc
:array-dimension-limit
))
2768 (error "bad dimension in array type: ~S" dim
))))
2771 (error "Array dimensions is not a list, integer or *:~% ~S" dims
))))
2775 (!define-type-method
(member :negate
) (type)
2776 (let ((xset (member-type-xset type
))
2777 (fp-zeroes (member-type-fp-zeroes type
)))
2779 ;; Hairy case, which needs to do a bit of float type
2780 ;; canonicalization.
2781 (apply #'type-intersection
2782 (if (xset-empty-p xset
)
2784 (make-negation-type (make-member-type xset nil
)))
2787 (let* ((opposite (neg-fp-zero x
))
2788 (type (ctype-of opposite
)))
2791 (modified-numeric-type type
:low nil
:high nil
))
2792 (modified-numeric-type type
:low nil
:high
(list opposite
))
2793 (make-eql-type opposite
)
2794 (modified-numeric-type type
:low
(list opposite
) :high nil
))))
2797 (make-negation-type type
))))
2799 (!define-type-method
(member :unparse
) (type)
2800 (cond ((eq type
(specifier-type 'null
)) 'null
) ; NULL type is EQ-comparable
2801 ((eq type
(specifier-type 'boolean
)) 'boolean
) ; so is BOOLEAN
2802 (t `(member ,@(member-type-members type
)))))
2804 (!define-type-method
(member :singleton-p
) (type)
2805 (if (eql 1 (member-type-size type
))
2806 (values t
(first (member-type-members type
)))
2809 (!define-type-method
(member :simple-subtypep
) (type1 type2
)
2810 (values (and (xset-subset-p (member-type-xset type1
)
2811 (member-type-xset type2
))
2812 (subsetp (member-type-fp-zeroes type1
)
2813 (member-type-fp-zeroes type2
)))
2816 (!define-type-method
(member :complex-subtypep-arg1
) (type1 type2
)
2818 (mapc-member-type-members
2820 (multiple-value-bind (ok surep
) (ctypep elt type2
)
2822 (return-from punt
(values nil nil
)))
2824 (return-from punt
(values nil t
)))))
2828 ;;; We punt if the odd type is enumerable and intersects with the
2829 ;;; MEMBER type. If not enumerable, then it is definitely not a
2830 ;;; subtype of the MEMBER type.
2831 (!define-type-method
(member :complex-subtypep-arg2
) (type1 type2
)
2832 (cond ((not (type-enumerable type1
)) (values nil t
))
2833 ((types-equal-or-intersect type1 type2
)
2834 (invoke-complex-subtypep-arg1-method type1 type2
))
2835 (t (values nil t
))))
2837 (!define-type-method
(member :simple-intersection2
) (type1 type2
)
2838 (make-member-type (xset-intersection (member-type-xset type1
)
2839 (member-type-xset type2
))
2840 (intersection (member-type-fp-zeroes type1
)
2841 (member-type-fp-zeroes type2
))))
2843 (!define-type-method
(member :complex-intersection2
) (type1 type2
)
2845 (let ((xset (alloc-xset))
2847 (mapc-member-type-members
2849 (multiple-value-bind (ok sure
) (ctypep member type1
)
2851 (return-from punt nil
))
2853 (if (fp-zero-p member
)
2854 (pushnew member fp-zeroes
)
2855 (add-to-xset member xset
)))))
2857 (if (and (xset-empty-p xset
) (not fp-zeroes
))
2859 (make-member-type xset fp-zeroes
)))))
2861 ;;; We don't need a :COMPLEX-UNION2, since the only interesting case is
2862 ;;; a union type, and the member/union interaction is handled by the
2863 ;;; union type method.
2864 (!define-type-method
(member :simple-union2
) (type1 type2
)
2865 (make-member-type (xset-union (member-type-xset type1
)
2866 (member-type-xset type2
))
2867 (union (member-type-fp-zeroes type1
)
2868 (member-type-fp-zeroes type2
))))
2870 (!define-type-method
(member :simple-
=) (type1 type2
)
2871 (let ((xset1 (member-type-xset type1
))
2872 (xset2 (member-type-xset type2
))
2873 (l1 (member-type-fp-zeroes type1
))
2874 (l2 (member-type-fp-zeroes type2
)))
2875 (values (and (eql (xset-count xset1
) (xset-count xset2
))
2876 (xset-subset-p xset1 xset2
)
2877 (xset-subset-p xset2 xset1
)
2882 (!define-type-method
(member :complex-
=) (type1 type2
)
2883 (if (type-enumerable type1
)
2884 (multiple-value-bind (val win
) (csubtypep type2 type1
)
2885 (if (or val
(not win
))
2890 (!def-type-translator member
:list
(&rest members
)
2892 (let (ms numbers char-codes
)
2893 (dolist (m (remove-duplicates members
))
2895 (character (push (sb!xc
:char-code m
) char-codes
))
2896 (real (if (and (floatp m
) (zerop m
))
2898 (push (ctype-of m
) numbers
)))
2901 (member-type-from-list ms
)
2902 (make-character-set-type (mapcar (lambda (x) (cons x x
))
2903 (sort char-codes
#'<)))
2904 (nreverse numbers
)))
2907 ;;;; intersection types
2909 ;;;; Until version 0.6.10.6, SBCL followed the original CMU CL approach
2910 ;;;; of punting on all AND types, not just the unreasonably complicated
2911 ;;;; ones. The change was motivated by trying to get the KEYWORD type
2912 ;;;; to behave sensibly:
2913 ;;;; ;; reasonable definition
2914 ;;;; (DEFTYPE KEYWORD () '(AND SYMBOL (SATISFIES KEYWORDP)))
2915 ;;;; ;; reasonable behavior
2916 ;;;; (AVER (SUBTYPEP 'KEYWORD 'SYMBOL))
2917 ;;;; Without understanding a little about the semantics of AND, we'd
2918 ;;;; get (SUBTYPEP 'KEYWORD 'SYMBOL)=>NIL,NIL and, for entirely
2919 ;;;; parallel reasons, (SUBTYPEP 'RATIO 'NUMBER)=>NIL,NIL. That's
2922 ;;;; We still follow the example of CMU CL to some extent, by punting
2923 ;;;; (to the opaque HAIRY-TYPE) on sufficiently complicated types
2926 (!define-type-class intersection
2927 :enumerable
#'compound-type-enumerable
2928 :might-contain-other-types t
)
2930 (!define-type-method
(intersection :negate
) (type)
2932 (mapcar #'type-negation
(intersection-type-types type
))))
2934 ;;; A few intersection types have special names. The others just get
2935 ;;; mechanically unparsed.
2936 (!define-type-method
(intersection :unparse
) (type)
2937 (declare (type ctype type
))
2938 (or (find type
'(ratio keyword compiled-function
) :key
#'specifier-type
:test
#'type
=)
2939 `(and ,@(mapcar #'type-specifier
(intersection-type-types type
)))))
2941 ;;; shared machinery for type equality: true if every type in the set
2942 ;;; TYPES1 matches a type in the set TYPES2 and vice versa
2943 (defun type=-set
(types1 types2
)
2944 (flet ((type<=-set
(x y
)
2945 (declare (type list x y
))
2946 (every/type
(lambda (x y-element
)
2947 (any/type
#'type
= y-element x
))
2949 (and/type
(type<=-set types1 types2
)
2950 (type<=-set types2 types1
))))
2952 ;;; Two intersection types are equal if their subtypes are equal sets.
2954 ;;; FIXME: Might it be better to use
2955 ;;; (AND (SUBTYPEP X Y) (SUBTYPEP Y X))
2956 ;;; instead, since SUBTYPEP is the usual relationship that we care
2957 ;;; most about, so it would be good to leverage any ingenuity there
2958 ;;; in this more obscure method?
2959 (!define-type-method
(intersection :simple-
=) (type1 type2
)
2960 (type=-set
(intersection-type-types type1
)
2961 (intersection-type-types type2
)))
2963 (defun %intersection-complex-subtypep-arg1
(type1 type2
)
2964 (type= type1
(type-intersection type1 type2
)))
2966 (defun %intersection-simple-subtypep
(type1 type2
)
2967 (every/type
#'%intersection-complex-subtypep-arg1
2969 (intersection-type-types type2
)))
2971 (!define-type-method
(intersection :simple-subtypep
) (type1 type2
)
2972 (%intersection-simple-subtypep type1 type2
))
2974 (!define-type-method
(intersection :complex-subtypep-arg1
) (type1 type2
)
2975 (%intersection-complex-subtypep-arg1 type1 type2
))
2977 (defun %intersection-complex-subtypep-arg2
(type1 type2
)
2978 (every/type
#'csubtypep type1
(intersection-type-types type2
)))
2980 (!define-type-method
(intersection :complex-subtypep-arg2
) (type1 type2
)
2981 (%intersection-complex-subtypep-arg2 type1 type2
))
2983 ;;; FIXME: This will look eeriely familiar to readers of the UNION
2984 ;;; :SIMPLE-INTERSECTION2 :COMPLEX-INTERSECTION2 method. That's
2985 ;;; because it was generated by cut'n'paste methods. Given that
2986 ;;; intersections and unions have all sorts of symmetries known to
2987 ;;; mathematics, it shouldn't be beyond the ken of some programmers to
2988 ;;; reflect those symmetries in code in a way that ties them together
2989 ;;; more strongly than having two independent near-copies :-/
2990 (!define-type-method
(intersection :simple-union2
:complex-union2
)
2992 ;; Within this method, type2 is guaranteed to be an intersection
2994 (aver (intersection-type-p type2
))
2995 ;; Make sure to call only the applicable methods...
2996 (cond ((and (intersection-type-p type1
)
2997 (%intersection-simple-subtypep type1 type2
)) type2
)
2998 ((and (intersection-type-p type1
)
2999 (%intersection-simple-subtypep type2 type1
)) type1
)
3000 ((and (not (intersection-type-p type1
))
3001 (%intersection-complex-subtypep-arg2 type1 type2
))
3003 ((and (not (intersection-type-p type1
))
3004 (%intersection-complex-subtypep-arg1 type2 type1
))
3006 ;; KLUDGE: This special (and somewhat hairy) magic is required
3007 ;; to deal with the RATIONAL/INTEGER special case. The UNION
3008 ;; of (INTEGER * -1) and (AND (RATIONAL * -1/2) (NOT INTEGER))
3009 ;; should be (RATIONAL * -1/2) -- CSR, 2003-02-28
3010 ((and (csubtypep type2
(specifier-type 'ratio
))
3011 (numeric-type-p type1
)
3012 (csubtypep type1
(specifier-type 'integer
))
3017 :low
(if (null (numeric-type-low type1
))
3019 (list (1- (numeric-type-low type1
))))
3020 :high
(if (null (numeric-type-high type1
))
3022 (list (1+ (numeric-type-high type1
)))))))
3023 (let* ((intersected (intersection-type-types type2
))
3024 (remaining (remove (specifier-type '(not integer
))
3027 (and (not (equal intersected remaining
))
3028 (type-union type1
(apply #'type-intersection remaining
)))))
3030 (let ((accumulator *universal-type
*))
3031 (do ((t2s (intersection-type-types type2
) (cdr t2s
)))
3032 ((null t2s
) accumulator
)
3033 (let ((union (type-union type1
(car t2s
))))
3034 (when (union-type-p union
)
3035 ;; we have to give up here -- there are all sorts of
3036 ;; ordering worries, but it's better than before.
3037 ;; Doing exactly the same as in the UNION
3038 ;; :SIMPLE/:COMPLEX-INTERSECTION2 method causes stack
3039 ;; overflow with the mutual recursion never bottoming
3041 (if (and (eq accumulator
*universal-type
*)
3043 ;; KLUDGE: if we get here, we have a partially
3044 ;; simplified result. While this isn't by any
3045 ;; means a universal simplification, including
3046 ;; this logic here means that we can get (OR
3047 ;; KEYWORD (NOT KEYWORD)) canonicalized to T.
3051 (type-intersection accumulator union
))))))))
3053 (!def-type-translator and
:list
((:context context
) &rest type-specifiers
)
3054 (apply #'type-intersection
3055 (mapcar (lambda (x) (specifier-type-r context x
))
3060 (!define-type-class union
3061 :enumerable
#'compound-type-enumerable
3062 :might-contain-other-types t
)
3064 (!define-type-method
(union :negate
) (type)
3065 (declare (type ctype type
))
3066 (apply #'type-intersection
3067 (mapcar #'type-negation
(union-type-types type
))))
3069 ;;; Unlike ARRAY-TYPE-DIMENSIONS this handles union types, which
3070 ;;; includes the type STRING.
3071 (defun ctype-array-dimensions (type)
3072 (labels ((process-compound-type (types)
3074 (dolist (type types
)
3075 (unless (or (hairy-type-p type
)
3076 (negation-type-p type
))
3077 (let ((current-dimensions (determine type
)))
3078 (cond ((eq current-dimensions
'*)
3079 (return-from ctype-array-dimensions
'*))
3081 (not (equal current-dimensions dimensions
)))
3082 (if (= (length dimensions
)
3083 (length current-dimensions
))
3085 (loop for dimension in dimensions
3086 for current-dimension in current-dimensions
3087 collect
(if (eql dimension current-dimension
)
3090 (return-from ctype-array-dimensions
'*)))
3093 (setf dimensions current-dimensions
))))))
3098 (array-type-dimensions type
))
3100 (process-compound-type (union-type-types type
)))
3102 (process-compound-type
3103 (mapcar #'ctype-of
(member-type-members type
))))
3105 (process-compound-type (intersection-type-types type
))))))
3108 (defun ctype-array-specialized-element-types (type)
3110 (labels ((process-compound-type (types)
3111 (loop for type in types
3112 unless
(or (hairy-type-p type
)
3113 (negation-type-p type
))
3114 do
(determine type
)))
3118 (when (eq (array-type-specialized-element-type type
) *wild-type
*)
3119 (return-from ctype-array-specialized-element-types
3121 (pushnew (array-type-specialized-element-type type
)
3122 types
:test
#'type
=))
3124 (process-compound-type (union-type-types type
)))
3126 (process-compound-type (intersection-type-types type
)))
3128 (process-compound-type
3129 (mapcar #'ctype-of
(member-type-members type
)))))))
3133 (defun unparse-string-type (ctype string-type
)
3134 (let ((string-ctype (specifier-type string-type
)))
3135 (and (union-type-p ctype
)
3136 (csubtypep ctype string-ctype
)
3137 (let ((types (copy-list (union-type-types string-ctype
))))
3138 (and (loop for type in
(union-type-types ctype
)
3139 for matching
= (and (array-type-p type
)
3143 do
(setf types
(delete matching types
)))
3145 (let ((dimensions (ctype-array-dimensions ctype
)))
3146 (cond ((and (singleton-p dimensions
)
3147 (integerp (car dimensions
)))
3148 `(,string-type
,@dimensions
)))))))
3150 ;;; The LIST, FLOAT and REAL types have special names. Other union
3151 ;;; types just get mechanically unparsed.
3152 (!define-type-method
(union :unparse
) (type)
3153 (declare (type ctype type
))
3155 ((type= type
(specifier-type 'list
)) 'list
)
3156 ((type= type
(specifier-type 'float
)) 'float
)
3157 ((type= type
(specifier-type 'real
)) 'real
)
3158 ((type= type
(specifier-type 'sequence
)) 'sequence
)
3159 ((type= type
(specifier-type 'bignum
)) 'bignum
)
3160 ((type= type
(specifier-type 'simple-string
)) 'simple-string
)
3161 ((type= type
(specifier-type 'string
)) 'string
)
3162 ((unparse-string-type type
'simple-string
))
3163 ((unparse-string-type type
'string
))
3164 ((type= type
(specifier-type 'complex
)) 'complex
)
3165 (t `(or ,@(mapcar #'type-specifier
(union-type-types type
))))))
3167 ;;; Two union types are equal if they are each subtypes of each
3168 ;;; other. We need to be this clever because our complex subtypep
3169 ;;; methods are now more accurate; we don't get infinite recursion
3170 ;;; because the simple-subtypep method delegates to complex-subtypep
3171 ;;; of the individual types of type1. - CSR, 2002-04-09
3173 ;;; Previous comment, now obsolete, but worth keeping around because
3174 ;;; it is true, though too strong a condition:
3176 ;;; Two union types are equal if their subtypes are equal sets.
3177 (!define-type-method
(union :simple-
=) (type1 type2
)
3178 (multiple-value-bind (subtype certain?
)
3179 (csubtypep type1 type2
)
3181 (csubtypep type2 type1
)
3182 ;; we might as well become as certain as possible.
3185 (multiple-value-bind (subtype certain?
)
3186 (csubtypep type2 type1
)
3187 (declare (ignore subtype
))
3188 (values nil certain?
))))))
3190 (!define-type-method
(union :complex-
=) (type1 type2
)
3191 (declare (ignore type1
))
3192 (if (some #'type-might-contain-other-types-p
3193 (union-type-types type2
))
3197 ;;; Similarly, a union type is a subtype of another if and only if
3198 ;;; every element of TYPE1 is a subtype of TYPE2.
3199 (defun union-simple-subtypep (type1 type2
)
3200 (every/type
(swapped-args-fun #'union-complex-subtypep-arg2
)
3202 (union-type-types type1
)))
3204 (!define-type-method
(union :simple-subtypep
) (type1 type2
)
3205 (union-simple-subtypep type1 type2
))
3207 (defun union-complex-subtypep-arg1 (type1 type2
)
3208 (every/type
(swapped-args-fun #'csubtypep
)
3210 (union-type-types type1
)))
3212 (!define-type-method
(union :complex-subtypep-arg1
) (type1 type2
)
3213 (union-complex-subtypep-arg1 type1 type2
))
3215 (defun union-complex-subtypep-arg2 (type1 type2
)
3216 ;; At this stage, we know that type2 is a union type and type1
3217 ;; isn't. We might as well check this, though:
3218 (aver (union-type-p type2
))
3219 (aver (not (union-type-p type1
)))
3220 ;; was: (any/type #'csubtypep type1 (union-type-types type2)), which
3221 ;; turns out to be too restrictive, causing bug 91.
3223 ;; the following reimplementation might look dodgy. It is dodgy. It
3224 ;; depends on the union :complex-= method not doing very much work
3225 ;; -- certainly, not using subtypep. Reasoning:
3227 ;; A is a subset of (B1 u B2)
3228 ;; <=> A n (B1 u B2) = A
3229 ;; <=> (A n B1) u (A n B2) = A
3231 ;; But, we have to be careful not to delegate this type= to
3232 ;; something that could invoke subtypep, which might get us back
3233 ;; here -> stack explosion. We therefore ensure that the second type
3234 ;; (which is the one that's dispatched on) is either a union type
3235 ;; (where we've ensured that the complex-= method will not call
3236 ;; subtypep) or something with no union types involved, in which
3237 ;; case we'll never come back here.
3239 ;; If we don't do this, then e.g.
3240 ;; (SUBTYPEP '(MEMBER 3) '(OR (SATISFIES FOO) (SATISFIES BAR)))
3241 ;; would loop infinitely, as the member :complex-= method is
3242 ;; implemented in terms of subtypep.
3244 ;; Ouch. - CSR, 2002-04-10
3245 (multiple-value-bind (sub-value sub-certain?
)
3248 (mapcar (lambda (x) (type-intersection type1 x
))
3249 (union-type-types type2
))))
3251 (values sub-value sub-certain?
)
3252 ;; The ANY/TYPE expression above is a sufficient condition for
3253 ;; subsetness, but not a necessary one, so we might get a more
3254 ;; certain answer by this CALL-NEXT-METHOD-ish step when the
3255 ;; ANY/TYPE expression is uncertain.
3256 (invoke-complex-subtypep-arg1-method type1 type2
))))
3258 (!define-type-method
(union :complex-subtypep-arg2
) (type1 type2
)
3259 (union-complex-subtypep-arg2 type1 type2
))
3261 (!define-type-method
(union :simple-intersection2
:complex-intersection2
)
3263 ;; The CSUBTYPEP clauses here let us simplify e.g.
3264 ;; (TYPE-INTERSECTION2 (SPECIFIER-TYPE 'LIST)
3265 ;; (SPECIFIER-TYPE '(OR LIST VECTOR)))
3266 ;; (where LIST is (OR CONS NULL)).
3268 ;; The tests are more or less (CSUBTYPEP TYPE1 TYPE2) and vice
3269 ;; versa, but it's important that we pre-expand them into
3270 ;; specialized operations on individual elements of
3271 ;; UNION-TYPE-TYPES, instead of using the ordinary call to
3272 ;; CSUBTYPEP, in order to avoid possibly invoking any methods which
3273 ;; might in turn invoke (TYPE-INTERSECTION2 TYPE1 TYPE2) and thus
3274 ;; cause infinite recursion.
3276 ;; Within this method, type2 is guaranteed to be a union type:
3277 (aver (union-type-p type2
))
3278 ;; Make sure to call only the applicable methods...
3279 (cond ((and (union-type-p type1
)
3280 (union-simple-subtypep type1 type2
)) type1
)
3281 ((and (union-type-p type1
)
3282 (union-simple-subtypep type2 type1
)) type2
)
3283 ((and (not (union-type-p type1
))
3284 (union-complex-subtypep-arg2 type1 type2
))
3286 ((and (not (union-type-p type1
))
3287 (union-complex-subtypep-arg1 type2 type1
))
3290 ;; KLUDGE: This code accumulates a sequence of TYPE-UNION2
3291 ;; operations in a particular order, and gives up if any of
3292 ;; the sub-unions turn out not to be simple. In other cases
3293 ;; ca. sbcl-0.6.11.15, that approach to taking a union was a
3294 ;; bad idea, since it can overlook simplifications which
3295 ;; might occur if the terms were accumulated in a different
3296 ;; order. It's possible that that will be a problem here too.
3297 ;; However, I can't think of a good example to demonstrate
3298 ;; it, and without an example to demonstrate it I can't write
3299 ;; test cases, and without test cases I don't want to
3300 ;; complicate the code to address what's still a hypothetical
3301 ;; problem. So I punted. -- WHN 2001-03-20
3302 (let ((accumulator *empty-type
*))
3303 (dolist (t2 (union-type-types type2
) accumulator
)
3305 (type-union accumulator
3306 (type-intersection type1 t2
))))))))
3308 (!def-type-translator or
:list
((:context context
) &rest type-specifiers
)
3309 (let ((type (apply #'type-union
3310 (mapcar (lambda (x) (specifier-type-r context x
))
3312 (if (union-type-p type
)
3313 (sb!kernel
::simplify-array-unions type
)
3318 (!def-type-translator cons
((:context context
)
3319 &optional
(car-type-spec '*) (cdr-type-spec '*))
3320 (let ((car-type (single-value-specifier-type-r context car-type-spec
))
3321 (cdr-type (single-value-specifier-type-r context cdr-type-spec
)))
3322 (make-cons-type car-type cdr-type
)))
3324 (!define-type-method
(cons :negate
) (type)
3325 (if (and (eq (cons-type-car-type type
) *universal-type
*)
3326 (eq (cons-type-cdr-type type
) *universal-type
*))
3327 (make-negation-type type
)
3329 (make-negation-type (specifier-type 'cons
))
3331 ((and (not (eq (cons-type-car-type type
) *universal-type
*))
3332 (not (eq (cons-type-cdr-type type
) *universal-type
*)))
3335 (type-negation (cons-type-car-type type
))
3339 (type-negation (cons-type-cdr-type type
)))))
3340 ((not (eq (cons-type-car-type type
) *universal-type
*))
3342 (type-negation (cons-type-car-type type
))
3344 ((not (eq (cons-type-cdr-type type
) *universal-type
*))
3347 (type-negation (cons-type-cdr-type type
))))
3348 (t (bug "Weird CONS type ~S" type
))))))
3350 (!define-type-method
(cons :unparse
) (type)
3351 (if (eq type
(specifier-type 'cons
))
3353 `(cons ,(type-specifier (cons-type-car-type type
))
3354 ,(type-specifier (cons-type-cdr-type type
)))))
3356 (!define-type-method
(cons :simple-
=) (type1 type2
)
3357 (declare (type cons-type type1 type2
))
3358 (multiple-value-bind (car-match car-win
)
3359 (type= (cons-type-car-type type1
) (cons-type-car-type type2
))
3360 (multiple-value-bind (cdr-match cdr-win
)
3361 (type= (cons-type-cdr-type type1
) (cons-type-cdr-type type2
))
3362 (cond ((and car-match cdr-match
)
3363 (aver (and car-win cdr-win
))
3367 ;; FIXME: Ideally we would like to detect and handle
3368 ;; (CONS UNKNOWN INTEGER) (CONS UNKNOWN SYMBOL) => NIL, T
3369 ;; but just returning a secondary true on (and car-win cdr-win)
3370 ;; unfortunately breaks other things. --NS 2006-08-16
3371 (and (or (and (not car-match
) car-win
)
3372 (and (not cdr-match
) cdr-win
))
3373 (not (and (cons-type-might-be-empty-type type1
)
3374 (cons-type-might-be-empty-type type2
))))))))))
3376 (!define-type-method
(cons :simple-subtypep
) (type1 type2
)
3377 (declare (type cons-type type1 type2
))
3378 (multiple-value-bind (val-car win-car
)
3379 (csubtypep (cons-type-car-type type1
) (cons-type-car-type type2
))
3380 (multiple-value-bind (val-cdr win-cdr
)
3381 (csubtypep (cons-type-cdr-type type1
) (cons-type-cdr-type type2
))
3382 (if (and val-car val-cdr
)
3383 (values t
(and win-car win-cdr
))
3384 (values nil
(or (and (not val-car
) win-car
)
3385 (and (not val-cdr
) win-cdr
)))))))
3387 ;;; Give up if a precise type is not possible, to avoid returning
3388 ;;; overly general types.
3389 (!define-type-method
(cons :simple-union2
) (type1 type2
)
3390 (declare (type cons-type type1 type2
))
3391 (let ((car-type1 (cons-type-car-type type1
))
3392 (car-type2 (cons-type-car-type type2
))
3393 (cdr-type1 (cons-type-cdr-type type1
))
3394 (cdr-type2 (cons-type-cdr-type type2
))
3397 ;; UGH. -- CSR, 2003-02-24
3398 (macrolet ((frob-car (car1 car2 cdr1 cdr2
3399 &optional
(not1 nil not1p
))
3401 (make-cons-type ,car1
(type-union ,cdr1
,cdr2
))
3403 (type-intersection ,car2
3406 `(type-negation ,car1
)))
3408 (cond ((type= car-type1 car-type2
)
3409 (make-cons-type car-type1
3410 (type-union cdr-type1 cdr-type2
)))
3411 ((type= cdr-type1 cdr-type2
)
3412 (make-cons-type (type-union car-type1 car-type2
)
3414 ((csubtypep car-type1 car-type2
)
3415 (frob-car car-type1 car-type2 cdr-type1 cdr-type2
))
3416 ((csubtypep car-type2 car-type1
)
3417 (frob-car car-type2 car-type1 cdr-type2 cdr-type1
))
3418 ;; more general case of the above, but harder to compute
3420 (setf car-not1
(type-negation car-type1
))
3421 (multiple-value-bind (yes win
)
3422 (csubtypep car-type2 car-not1
)
3423 (and (not yes
) win
)))
3424 (frob-car car-type1 car-type2 cdr-type1 cdr-type2 car-not1
))
3426 (setf car-not2
(type-negation car-type2
))
3427 (multiple-value-bind (yes win
)
3428 (csubtypep car-type1 car-not2
)
3429 (and (not yes
) win
)))
3430 (frob-car car-type2 car-type1 cdr-type2 cdr-type1 car-not2
))
3431 ;; Don't put these in -- consider the effect of taking the
3432 ;; union of (CONS (INTEGER 0 2) (INTEGER 5 7)) and
3433 ;; (CONS (INTEGER 0 3) (INTEGER 5 6)).
3435 ((csubtypep cdr-type1 cdr-type2
)
3436 (frob-cdr car-type1 car-type2 cdr-type1 cdr-type2
))
3438 ((csubtypep cdr-type2 cdr-type1
)
3439 (frob-cdr car-type2 car-type1 cdr-type2 cdr-type1
))))))
3441 (!define-type-method
(cons :simple-intersection2
) (type1 type2
)
3442 (declare (type cons-type type1 type2
))
3443 (let ((car-int2 (type-intersection2 (cons-type-car-type type1
)
3444 (cons-type-car-type type2
)))
3445 (cdr-int2 (type-intersection2 (cons-type-cdr-type type1
)
3446 (cons-type-cdr-type type2
))))
3448 ((and car-int2 cdr-int2
) (make-cons-type car-int2 cdr-int2
))
3449 (car-int2 (make-cons-type car-int2
3451 (cons-type-cdr-type type1
)
3452 (cons-type-cdr-type type2
))))
3453 (cdr-int2 (make-cons-type
3454 (type-intersection (cons-type-car-type type1
)
3455 (cons-type-car-type type2
))
3458 (!define-superclasses cons
((cons)) !cold-init-forms
)
3460 ;;;; CHARACTER-SET types
3462 (!def-type-translator character-set
3463 (&optional
(pairs '((0 .
#.
(1- sb
!xc
:char-code-limit
)))))
3464 (make-character-set-type pairs
))
3466 (!define-type-method
(character-set :negate
) (type)
3467 (let ((pairs (character-set-type-pairs type
)))
3468 (if (and (= (length pairs
) 1)
3470 (= (cdar pairs
) (1- sb
!xc
:char-code-limit
)))
3471 (make-negation-type type
)
3472 (let ((not-character
3474 (make-character-set-type
3475 '((0 .
#.
(1- sb
!xc
:char-code-limit
)))))))
3478 (make-character-set-type
3480 (when (> (caar pairs
) 0)
3481 (push (cons 0 (1- (caar pairs
))) not-pairs
))
3482 (do* ((tail pairs
(cdr tail
))
3483 (high1 (cdar tail
) (cdar tail
))
3484 (low2 (caadr tail
) (caadr tail
)))
3486 (when (< (cdar tail
) (1- sb
!xc
:char-code-limit
))
3487 (push (cons (1+ (cdar tail
))
3488 (1- sb
!xc
:char-code-limit
))
3490 (nreverse not-pairs
))
3491 (push (cons (1+ high1
) (1- low2
)) not-pairs
)))))))))
3493 (!define-type-method
(character-set :unparse
) (type)
3495 ((eq type
(specifier-type 'character
)) 'character
)
3496 ((eq type
(specifier-type 'base-char
)) 'base-char
)
3497 ((eq type
(specifier-type 'extended-char
)) 'extended-char
)
3498 ;; standard-char is not an interned type
3499 ((type= type
(specifier-type 'standard-char
)) 'standard-char
)
3501 ;; Unparse into either MEMBER or CHARACTER-SET. We use MEMBER if there
3502 ;; are at most as many characters as there are character code ranges.
3503 ;; (basically saying to use MEMBER if each range is one character)
3504 (let* ((pairs (character-set-type-pairs type
))
3505 (count (length pairs
))
3506 (chars (loop named outer
3507 for
(low . high
) in pairs
3508 nconc
(loop for code from low upto high
3509 collect
(sb!xc
:code-char code
)
3510 when
(minusp (decf count
))
3511 do
(return-from outer t
)))))
3513 `(character-set ,pairs
)
3514 `(member ,@chars
))))))
3516 (!define-type-method
(character-set :singleton-p
) (type)
3517 (let* ((pairs (character-set-type-pairs type
))
3518 (pair (first pairs
)))
3519 (if (and (typep pairs
'(cons t null
))
3520 (eql (car pair
) (cdr pair
)))
3521 (values t
(code-char (car pair
)))
3524 (!define-type-method
(character-set :simple-
=) (type1 type2
)
3525 (let ((pairs1 (character-set-type-pairs type1
))
3526 (pairs2 (character-set-type-pairs type2
)))
3527 (values (equal pairs1 pairs2
) t
)))
3529 (!define-type-method
(character-set :simple-subtypep
) (type1 type2
)
3531 (dolist (pair (character-set-type-pairs type1
) t
)
3532 (unless (position pair
(character-set-type-pairs type2
)
3533 :test
(lambda (x y
) (and (>= (car x
) (car y
))
3534 (<= (cdr x
) (cdr y
)))))
3538 (!define-type-method
(character-set :simple-union2
) (type1 type2
)
3539 ;; KLUDGE: the canonizing in the MAKE-CHARACTER-SET-TYPE function
3540 ;; actually does the union for us. It might be a little fragile to
3542 (make-character-set-type
3544 (copy-alist (character-set-type-pairs type1
))
3545 (copy-alist (character-set-type-pairs type2
))
3548 (!define-type-method
(character-set :simple-intersection2
) (type1 type2
)
3549 ;; KLUDGE: brute force.
3552 (dolist (pair1 (character-set-type-pairs type1
)
3553 (make-character-set-type
3554 (sort pairs
#'< :key
#'car
)))
3555 (dolist (pair2 (character-set-type-pairs type2
))
3557 ((<= (car pair1
) (car pair2
) (cdr pair1
))
3558 (push (cons (car pair2
) (min (cdr pair1
) (cdr pair2
))) pairs
))
3559 ((<= (car pair2
) (car pair1
) (cdr pair2
))
3560 (push (cons (car pair1
) (min (cdr pair1
) (cdr pair2
))) pairs
))))))
3562 (make-character-set-type
3563 (intersect-type-pairs
3564 (character-set-type-pairs type1
)
3565 (character-set-type-pairs type2
))))
3568 ;;; Intersect two ordered lists of pairs
3569 ;;; Each list is of the form ((start1 . end1) ... (startn . endn)),
3570 ;;; where start1 <= end1 < start2 <= end2 < ... < startn <= endn.
3571 ;;; Each pair represents the integer interval start..end.
3573 (defun intersect-type-pairs (alist1 alist2
)
3574 (if (and alist1 alist2
)
3576 (pair1 (pop alist1
))
3577 (pair2 (pop alist2
)))
3579 (when (> (car pair1
) (car pair2
))
3580 (rotatef pair1 pair2
)
3581 (rotatef alist1 alist2
))
3582 (let ((pair1-cdr (cdr pair1
)))
3584 ((> (car pair2
) pair1-cdr
)
3585 ;; No over lap -- discard pair1
3586 (unless alist1
(return))
3587 (setq pair1
(pop alist1
)))
3588 ((<= (cdr pair2
) pair1-cdr
)
3589 (push (cons (car pair2
) (cdr pair2
)) res
)
3591 ((= (cdr pair2
) pair1-cdr
)
3592 (unless alist1
(return))
3593 (unless alist2
(return))
3594 (setq pair1
(pop alist1
)
3595 pair2
(pop alist2
)))
3596 (t ;; (< (cdr pair2) pair1-cdr)
3597 (unless alist2
(return))
3598 (setq pair1
(cons (1+ (cdr pair2
)) pair1-cdr
))
3599 (setq pair2
(pop alist2
)))))
3600 (t ;; (> (cdr pair2) (cdr pair1))
3601 (push (cons (car pair2
) pair1-cdr
) res
)
3602 (unless alist1
(return))
3603 (setq pair2
(cons (1+ pair1-cdr
) (cdr pair2
)))
3604 (setq pair1
(pop alist1
))))))
3609 ;;; Return the type that describes all objects that are in X but not
3610 ;;; in Y. If we can't determine this type, then return NIL.
3612 ;;; For now, we only are clever dealing with union and member types.
3613 ;;; If either type is not a union type, then we pretend that it is a
3614 ;;; union of just one type. What we do is remove from X all the types
3615 ;;; that are a subtype any type in Y. If any type in X intersects with
3616 ;;; a type in Y but is not a subtype, then we give up.
3618 ;;; We must also special-case any member type that appears in the
3619 ;;; union. We remove from X's members all objects that are TYPEP to Y.
3620 ;;; If Y has any members, we must be careful that none of those
3621 ;;; members are CTYPEP to any of Y's non-member types. We give up in
3622 ;;; this case, since to compute that difference we would have to break
3623 ;;; the type from X into some collection of types that represents the
3624 ;;; type without that particular element. This seems too hairy to be
3625 ;;; worthwhile, given its low utility.
3626 (defun type-difference (x y
)
3627 (if (and (numeric-type-p x
) (numeric-type-p y
))
3628 ;; Numeric types are easy. Are there any others we should handle like this?
3629 (type-intersection x
(type-negation y
))
3630 (let ((x-types (if (union-type-p x
) (union-type-types x
) (list x
)))
3631 (y-types (if (union-type-p y
) (union-type-types y
) (list y
))))
3633 (dolist (x-type x-types
)
3634 (if (member-type-p x-type
)
3635 (let ((xset (alloc-xset))
3637 (mapc-member-type-members
3639 (multiple-value-bind (ok sure
) (ctypep elt y
)
3641 (return-from type-difference nil
))
3644 (pushnew elt fp-zeroes
)
3645 (add-to-xset elt xset
)))))
3647 (unless (and (xset-empty-p xset
) (not fp-zeroes
))
3648 (res (make-member-type xset fp-zeroes
))))
3649 (dolist (y-type y-types
(res x-type
))
3650 (multiple-value-bind (val win
) (csubtypep x-type y-type
)
3651 (unless win
(return-from type-difference nil
))
3653 (when (types-equal-or-intersect x-type y-type
)
3654 (return-from type-difference nil
))))))
3655 (let ((y-mem (find-if #'member-type-p y-types
)))
3657 (dolist (x-type x-types
)
3658 (unless (member-type-p x-type
)
3659 (mapc-member-type-members
3661 (multiple-value-bind (ok sure
) (ctypep member x-type
)
3662 (when (or (not sure
) ok
)
3663 (return-from type-difference nil
))))
3665 (apply #'type-union
(res))))))
3667 (!def-type-translator array
((:context context
)
3668 &optional
(element-type '*)
3670 (let ((eltype (if (eq element-type
'*)
3672 (specifier-type-r context element-type
))))
3673 (make-array-type (canonical-array-dimensions dimensions
)
3675 :element-type eltype
3676 :specialized-element-type
(%upgraded-array-element-type
3679 (!def-type-translator simple-array
((:context context
)
3680 &optional
(element-type '*)
3682 (let ((eltype (if (eq element-type
'*)
3684 (specifier-type-r context element-type
))))
3685 (make-array-type (canonical-array-dimensions dimensions
)
3687 :element-type eltype
3688 :specialized-element-type
(%upgraded-array-element-type
3691 ;;;; SIMD-PACK types
3694 (!define-type-class simd-pack
:enumerable nil
3695 :might-contain-other-types nil
)
3697 ;; Though this involves a recursive call to parser, parsing context need not
3698 ;; be passed down, because an unknown-type condition is an immediate failure.
3699 (!def-type-translator simd-pack
(&optional
(element-type-spec '*))
3700 (if (eql element-type-spec
'*)
3701 (%make-simd-pack-type
*simd-pack-element-types
*)
3702 (make-simd-pack-type (single-value-specifier-type element-type-spec
))))
3704 (!define-type-method
(simd-pack :negate
) (type)
3705 (let ((remaining (set-difference *simd-pack-element-types
*
3706 (simd-pack-type-element-type type
)))
3707 (not-simd-pack (make-negation-type (specifier-type 'simd-pack
))))
3709 (type-union not-simd-pack
(%make-simd-pack-type remaining
))
3712 (!define-type-method
(simd-pack :unparse
) (type)
3713 (let ((eltypes (simd-pack-type-element-type type
)))
3714 (cond ((equal eltypes
*simd-pack-element-types
*)
3716 ((= 1 (length eltypes
))
3717 `(simd-pack ,(first eltypes
)))
3719 `(or ,@(mapcar (lambda (eltype)
3720 `(simd-pack ,eltype
))
3723 (!define-type-method
(simd-pack :simple-
=) (type1 type2
)
3724 (declare (type simd-pack-type type1 type2
))
3725 (null (set-exclusive-or (simd-pack-type-element-type type1
)
3726 (simd-pack-type-element-type type2
))))
3728 (!define-type-method
(simd-pack :simple-subtypep
) (type1 type2
)
3729 (declare (type simd-pack-type type1 type2
))
3730 (subsetp (simd-pack-type-element-type type1
)
3731 (simd-pack-type-element-type type2
)))
3733 (!define-type-method
(simd-pack :simple-union2
) (type1 type2
)
3734 (declare (type simd-pack-type type1 type2
))
3735 (%make-simd-pack-type
(union (simd-pack-type-element-type type1
)
3736 (simd-pack-type-element-type type2
))))
3738 (!define-type-method
(simd-pack :simple-intersection2
) (type1 type2
)
3739 (declare (type simd-pack-type type1 type2
))
3740 (let ((intersection (intersection (simd-pack-type-element-type type1
)
3741 (simd-pack-type-element-type type2
))))
3743 (%make-simd-pack-type intersection
)
3746 (!define-superclasses simd-pack
((simd-pack)) !cold-init-forms
))
3748 ;;;; utilities shared between cross-compiler and target system
3750 ;;; Does the type derived from compilation of an actual function
3751 ;;; definition satisfy declarations of a function's type?
3752 (defun defined-ftype-matches-declared-ftype-p (defined-ftype declared-ftype
)
3753 (declare (type ctype defined-ftype declared-ftype
))
3754 (flet ((is-built-in-class-function-p (ctype)
3755 (and (built-in-classoid-p ctype
)
3756 (eq (built-in-classoid-name ctype
) 'function
))))
3757 (cond (;; DECLARED-FTYPE could certainly be #<BUILT-IN-CLASS FUNCTION>;
3758 ;; that's what happens when we (DECLAIM (FTYPE FUNCTION FOO)).
3759 (is-built-in-class-function-p declared-ftype
)
3760 ;; In that case, any definition satisfies the declaration.
3762 (;; It's not clear whether or how DEFINED-FTYPE might be
3763 ;; #<BUILT-IN-CLASS FUNCTION>, but it's not obviously
3764 ;; invalid, so let's handle that case too, just in case.
3765 (is-built-in-class-function-p defined-ftype
)
3766 ;; No matter what DECLARED-FTYPE might be, we can't prove
3767 ;; that an object of type FUNCTION doesn't satisfy it, so
3768 ;; we return success no matter what.
3770 (;; Otherwise both of them must be FUN-TYPE objects.
3772 ;; FIXME: For now we only check compatibility of the return
3773 ;; type, not argument types, and we don't even check the
3774 ;; return type very precisely (as per bug 94a). It would be
3775 ;; good to do a better job. Perhaps to check the
3776 ;; compatibility of the arguments, we should (1) redo
3777 ;; VALUES-TYPES-EQUAL-OR-INTERSECT as
3778 ;; ARGS-TYPES-EQUAL-OR-INTERSECT, and then (2) apply it to
3779 ;; the ARGS-TYPE slices of the FUN-TYPEs. (ARGS-TYPE
3780 ;; is a base class both of VALUES-TYPE and of FUN-TYPE.)
3781 (values-types-equal-or-intersect
3782 (fun-type-returns defined-ftype
)
3783 (fun-type-returns declared-ftype
))))))
3785 ;;; This messy case of CTYPE for NUMBER is shared between the
3786 ;;; cross-compiler and the target system.
3787 (defun ctype-of-number (x)
3788 (let ((num (if (complexp x
) (realpart x
) x
)))
3789 (multiple-value-bind (complexp low high
)
3791 (let ((imag (imagpart x
)))
3792 (values :complex
(min num imag
) (max num imag
)))
3793 (values :real num num
))
3794 (make-numeric-type :class
(etypecase num
3795 (integer (if (complexp x
)
3796 (if (integerp (imagpart x
))
3800 (rational 'rational
)
3802 :format
(and (floatp num
) (float-format-name num
))
3807 ;;; The following function is a generic driver for approximating
3808 ;;; set-valued functions over types. Putting this here because it'll
3809 ;;; probably be useful for a lot of type analyses.
3811 ;;; Let f be a function from values of type X to Y, e.g., ARRAY-RANK.
3813 ;;; We compute an over or under-approximation of the set
3815 ;;; F(TYPE) = { f(x) : x in TYPE /\ x in X } \subseteq Y
3817 ;;; via set-valued approximations of f, OVER and UNDER.
3819 ;;; These functions must have the property that
3820 ;;; Forall TYPE, OVER(TYPE) \superseteq F(TYPE) and
3821 ;;; Forall TYPE, UNDER(TYPE) \subseteq F(TYPE)
3823 ;;; The driver is also parameterised over the finite set
3826 ;;; Union, intersection and difference are binary functions to compute
3827 ;;; set union, intersection and difference. Top and bottom are the
3828 ;;; concrete representations for the universe and empty sets; we never
3829 ;;; call the set functions on top or bottom, so it's safe to use
3830 ;;; special values there.
3834 ;;; TYPE: the ctype for which we wish to approximate F(TYPE)
3835 ;;; OVERAPPROXIMATE: true if we wish to overapproximate, nil otherwise.
3836 ;;; You usually want T.
3837 ;;; UNION/INTERSECTION/DIFFERENCE: implementations of finite set operations.
3838 ;;; Conform to cl::(union/intersection/set-difference). Passing NIL will
3839 ;;; disable some cleverness and result in quicker computation of coarser
3840 ;;; approximations. However, passing difference without union and intersection
3841 ;;; will probably not end well.
3842 ;;; TOP/BOTTOM: concrete representation of the universe and empty set. Finite
3843 ;;; set operations are never called on TOP/BOTTOM, so it's safe to use special
3845 ;;; OVER/UNDER: the set-valued approximations of F.
3847 ;;; Implementation details.
3849 ;;; It's a straightforward walk down the type.
3850 ;;; Union types -> take the union of children, intersection ->
3851 ;;; intersect. There is some complication for negation types: we must
3852 ;;; not only negate the result, but also flip from overapproximating
3853 ;;; to underapproximating in the children (or vice versa).
3855 ;;; We represent sets as a pair of (negate-p finite-set) in order to
3856 ;;; support negation types.
3858 (declaim (inline generic-abstract-type-function
))
3859 (defun generic-abstract-type-function
3860 (type overapproximate
3861 union intersection difference
3864 (labels ((union* (x y
)
3865 ;; wrappers to avoid calling union/intersection on
3867 (cond ((or (eql x top
)
3873 (funcall union x y
))))
3874 (intersection* (x y
)
3875 (cond ((or (eql x bottom
)
3881 (funcall intersection x y
))))
3882 (unite (not-x-p x not-y-p y
)
3883 ;; if we only have one negated set, it's x.
3885 (rotatef not-x-p not-y-p
)
3887 (cond ((and not-x-p not-y-p
)
3888 ;; -x \/ -y = -(x /\ y)
3889 (normalize t
(intersection* x y
)))
3891 ;; -x \/ y = -(x \ y)
3901 (funcall difference x y
)))))
3903 (values nil
(union* x y
)))))
3904 (intersect (not-x-p x not-y-p y
)
3906 (rotatef not-x-p not-y-p
)
3908 (cond ((and not-x-p not-y-p
)
3909 ;; -x /\ -y = -(x \/ y)
3910 (normalize t
(union* x y
)))
3913 (cond ((or (eql x top
) (eql y bottom
))
3914 (values nil bottom
))
3920 (values nil
(funcall difference y x
)))))
3922 (values nil
(intersection* x y
)))))
3923 (normalize (not-x-p x
)
3924 ;; catch some easy cases of redundant negation.
3925 (cond ((not not-x-p
)
3933 (default (overapproximate)
3935 (if overapproximate top bottom
))
3936 (walk-union (types overapproximate
)
3937 ;; Only do this if union is provided.
3939 (return-from walk-union
(default overapproximate
)))
3940 ;; Reduce/union from bottom.
3941 (let ((not-acc-p nil
)
3943 (dolist (type types
(values not-acc-p acc
))
3944 (multiple-value-bind (not x
)
3945 (walk type overapproximate
)
3946 (setf (values not-acc-p acc
)
3947 (unite not-acc-p acc not x
)))
3948 ;; Early exit on top set.
3949 (when (and (eql acc top
)
3951 (return (values nil top
))))))
3952 (walk-intersection (types overapproximate
)
3953 ;; Skip if we don't know how to intersect sets
3954 (unless intersection
3955 (return-from walk-intersection
(default overapproximate
)))
3956 ;; Reduce/intersection from top
3957 (let ((not-acc-p nil
)
3959 (dolist (type types
(values not-acc-p acc
))
3960 (multiple-value-bind (not x
)
3961 (walk type overapproximate
)
3962 (setf (values not-acc-p acc
)
3963 (intersect not-acc-p acc not x
)))
3964 (when (and (eql acc bottom
)
3966 (return (values nil bottom
))))))
3967 (walk-negate (type overapproximate
)
3968 ;; Don't introduce negated types if we don't know how to
3971 (return-from walk-negate
(default overapproximate
)))
3972 (multiple-value-bind (not x
)
3973 (walk type
(not overapproximate
))
3974 (normalize (not not
) x
)))
3975 (walk (type overapproximate
)
3978 (walk-union (union-type-types type
) overapproximate
))
3979 ((cons (member or union
))
3980 (walk-union (rest type
) overapproximate
))
3982 (walk-intersection (intersection-type-types type
) overapproximate
))
3983 ((cons (member and intersection
))
3984 (walk-intersection (rest type
) overapproximate
))
3986 (walk-negate (negation-type-type type
) overapproximate
))
3988 (walk-negate (second type
) overapproximate
))
3996 (funcall under type
)
3997 (default nil
))))))))
3998 (multiple-value-call #'normalize
(walk type overapproximate
))))
3999 (declaim (notinline generic-abstract-type-function
))
4001 ;;; Standard list representation of sets. Use CL:* for the universe.
4002 (defun list-abstract-type-function (type over
&key under
(overapproximate t
))
4003 (declare (inline generic-abstract-type-function
))
4004 (generic-abstract-type-function
4005 type overapproximate
4006 #'union
#'intersection
#'set-difference
4010 (!defun-from-collected-cold-init-forms
!late-type-cold-init
)
4012 (/show0
"late-type.lisp end of file")