1 ;;;; This software is part of the SBCL system. See the README file for
4 ;;;; This software is derived from the CMU CL system, which was
5 ;;;; written at Carnegie Mellon University and released into the
6 ;;;; public domain. The software is in the public domain and is
7 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
8 ;;;; files for more information.
10 (in-package "SB!KERNEL")
12 (!begin-collecting-cold-init-forms
)
14 ;;; Has the type system been properly initialized? (I.e. is it OK to
16 (defvar *type-system-initialized
* #+sb-xc-host nil
) ; (set in cold load)
18 ;;;; representations of types
20 ;;; A HAIRY-TYPE represents anything too weird to be described
21 ;;; reasonably or to be useful, such as NOT, SATISFIES, unknown types,
22 ;;; and unreasonably complicated types involving AND. We just remember
23 ;;; the original type spec.
24 (defstruct (hairy-type (:include ctype
25 (class-info (type-class-or-lose 'hairy
))
27 (might-contain-other-types-p t
))
30 ;; the Common Lisp type-specifier of the type we represent
31 (specifier nil
:type t
))
33 (!define-type-class hairy
)
35 ;;; An UNKNOWN-TYPE is a type not known to the type system (not yet
36 ;;; defined). We make this distinction since we don't want to complain
37 ;;; about types that are hairy but defined.
38 (defstruct (unknown-type (:include hairy-type
)
41 ;;; ARGS-TYPE objects are used both to represent VALUES types and
42 ;;; to represent FUNCTION types.
43 (defstruct (args-type (:include ctype
)
46 ;; Lists of the type for each required and optional argument.
47 (required nil
:type list
)
48 (optional nil
:type list
)
49 ;; The type for the rest arg. NIL if there is no &REST arg.
50 (rest nil
:type
(or ctype null
))
51 ;; true if &KEY arguments are specified
52 (keyp nil
:type boolean
)
53 ;; list of KEY-INFO structures describing the &KEY arguments
54 (keywords nil
:type list
)
55 ;; true if other &KEY arguments are allowed
56 (allowp nil
:type boolean
))
58 (defstruct (values-type
60 (class-info (type-class-or-lose 'values
)))
61 (:constructor %make-values-type
)
63 (define-cached-synonym make-values-type
)
65 (!define-type-class values
)
67 ;;; (SPECIFIER-TYPE 'FUNCTION) and its subtypes
68 (defstruct (fun-type (:include args-type
69 (class-info (type-class-or-lose 'function
))))
70 ;; true if the arguments are unrestrictive, i.e. *
71 (wild-args nil
:type boolean
)
72 ;; type describing the return values. This is a values type
73 ;; when multiple values were specified for the return.
74 (returns (missing-arg) :type ctype
))
76 ;;; The CONSTANT-TYPE structure represents a use of the CONSTANT-ARG
77 ;;; "type specifier", which is only meaningful in function argument
78 ;;; type specifiers used within the compiler. (It represents something
79 ;;; that the compiler knows to be a constant.)
80 (defstruct (constant-type
82 (class-info (type-class-or-lose 'constant
)))
84 ;; The type which the argument must be a constant instance of for this type
86 (type (missing-arg) :type ctype
))
88 ;;; The NAMED-TYPE is used to represent *, T and NIL. These types must
89 ;;; be super- or sub-types of all types, not just classes and * and
90 ;;; NIL aren't classes anyway, so it wouldn't make much sense to make
91 ;;; them built-in classes.
92 (defstruct (named-type (:include ctype
93 (class-info (type-class-or-lose 'named
)))
95 (name nil
:type symbol
))
97 ;;; a list of all the float "formats" (i.e. internal representations;
98 ;;; nothing to do with #'FORMAT), in order of decreasing precision
99 (eval-when (:compile-toplevel
:load-toplevel
:execute
)
100 (defparameter *float-formats
*
101 '(long-float double-float single-float short-float
)))
103 ;;; The type of a float format.
104 (deftype float-format
() `(member ,@*float-formats
*))
106 ;;; A NUMERIC-TYPE represents any numeric type, including things
108 (defstruct (numeric-type (:include ctype
109 (class-info (type-class-or-lose 'number
)))
110 (:constructor %make-numeric-type
)
112 ;; the kind of numeric type we have, or NIL if not specified (just
113 ;; NUMBER or COMPLEX)
115 ;; KLUDGE: A slot named CLASS for a non-CLASS value is bad.
116 ;; Especially when a CLASS value *is* stored in another slot (called
117 ;; CLASS-INFO:-). Perhaps this should be called CLASS-NAME? Also
118 ;; weird that comment above says "Numeric-Type is used to represent
119 ;; all numeric types" but this slot doesn't allow COMPLEX as an
120 ;; option.. how does this fall into "not specified" NIL case above?
121 ;; Perhaps someday we can switch to CLOS and make NUMERIC-TYPE
122 ;; be an abstract base class and INTEGER-TYPE, RATIONAL-TYPE, and
123 ;; whatnot be concrete subclasses..
124 (class nil
:type
(member integer rational float nil
) :read-only t
)
125 ;; "format" for a float type (i.e. type specifier for a CPU
126 ;; representation of floating point, e.g. 'SINGLE-FLOAT -- nothing
127 ;; to do with #'FORMAT), or NIL if not specified or not a float.
128 ;; Formats which don't exist in a given implementation don't appear
130 (format nil
:type
(or float-format null
) :read-only t
)
131 ;; Is this a complex numeric type? Null if unknown (only in NUMBER).
133 ;; FIXME: I'm bewildered by FOO-P names for things not intended to
134 ;; interpreted as truth values. Perhaps rename this COMPLEXNESS?
135 (complexp :real
:type
(member :real
:complex nil
) :read-only t
)
136 ;; The upper and lower bounds on the value, or NIL if there is no
137 ;; bound. If a list of a number, the bound is exclusive. Integer
138 ;; types never have exclusive bounds, i.e. they may have them on
139 ;; input, but they're canonicalized to inclusive bounds before we
141 (low nil
:type
(or number cons null
) :read-only t
)
142 (high nil
:type
(or number cons null
) :read-only t
))
144 ;;; Impose canonicalization rules for NUMERIC-TYPE. Note that in some
145 ;;; cases, despite the name, we return *EMPTY-TYPE* instead of a
147 (defun make-numeric-type (&key class format
(complexp :real
) low high
149 ;; if interval is empty
152 (if (or (consp low
) (consp high
)) ; if either bound is exclusive
153 (>= (type-bound-number low
) (type-bound-number high
))
156 (multiple-value-bind (canonical-low canonical-high
)
159 ;; INTEGER types always have their LOW and HIGH bounds
160 ;; represented as inclusive, not exclusive values.
161 (values (if (consp low
)
162 (1+ (type-bound-number low
))
165 (1- (type-bound-number high
))
167 #!+negative-zero-is-not-zero
169 ;; Canonicalize a low bound of (-0.0) to 0.0, and a high
170 ;; bound of (+0.0) to -0.0.
171 (values (if (and (consp low
)
174 (minusp (float-sign (car low
))))
175 (float 0.0 (car low
))
177 (if (and (consp high
)
180 (plusp (float-sign (car high
))))
181 (float -
0.0 (car high
))
184 ;; no canonicalization necessary
186 (%make-numeric-type
:class class
191 :enumerable enumerable
))))
193 (defun modified-numeric-type (base
195 (class (numeric-type-class base
))
196 (format (numeric-type-format base
))
197 (complexp (numeric-type-complexp base
))
198 (low (numeric-type-low base
))
199 (high (numeric-type-high base
))
200 (enumerable (numeric-type-enumerable base
)))
201 (make-numeric-type :class class
206 :enumerable enumerable
))
208 ;;; An ARRAY-TYPE is used to represent any array type, including
209 ;;; things such as SIMPLE-STRING.
210 (defstruct (array-type (:include ctype
211 (class-info (type-class-or-lose 'array
)))
212 (:constructor %make-array-type
)
214 ;; the dimensions of the array, or * if unspecified. If a dimension
215 ;; is unspecified, it is *.
216 (dimensions '* :type
(or list
(member *)))
217 ;; Is this not a simple array type? (:MAYBE means that we don't know.)
218 (complexp :maybe
:type
(member t nil
:maybe
))
219 ;; the element type as originally specified
220 (element-type (missing-arg) :type ctype
)
221 ;; the element type as it is specialized in this implementation
222 (specialized-element-type *wild-type
* :type ctype
))
223 (define-cached-synonym make-array-type
)
225 ;;; A MEMBER-TYPE represent a use of the MEMBER type specifier. We
226 ;;; bother with this at this level because MEMBER types are fairly
227 ;;; important and union and intersection are well defined.
228 (defstruct (member-type (:include ctype
229 (class-info (type-class-or-lose 'member
))
232 #-sb-xc-host
(:pure nil
))
233 ;; the things in the set, with no duplications
234 (members nil
:type list
))
236 ;;; A COMPOUND-TYPE is a type defined out of a set of types, the
237 ;;; common parent of UNION-TYPE and INTERSECTION-TYPE.
238 (defstruct (compound-type (:include ctype
239 (might-contain-other-types-p t
))
242 (types nil
:type list
:read-only t
))
244 ;;; A UNION-TYPE represents a use of the OR type specifier which we
245 ;;; couldn't canonicalize to something simpler. Canonical form:
246 ;;; 1. All possible pairwise simplifications (using the UNION2 type
247 ;;; methods) have been performed. Thus e.g. there is never more
248 ;;; than one MEMBER-TYPE component. FIXME: As of sbcl-0.6.11.13,
249 ;;; this hadn't been fully implemented yet.
250 ;;; 2. There are never any UNION-TYPE components.
251 (defstruct (union-type (:include compound-type
252 (class-info (type-class-or-lose 'union
)))
253 (:constructor %make-union-type
(enumerable types
))
255 (define-cached-synonym make-union-type
)
257 ;;; An INTERSECTION-TYPE represents a use of the AND type specifier
258 ;;; which we couldn't canonicalize to something simpler. Canonical form:
259 ;;; 1. All possible pairwise simplifications (using the INTERSECTION2
260 ;;; type methods) have been performed. Thus e.g. there is never more
261 ;;; than one MEMBER-TYPE component.
262 ;;; 2. There are never any INTERSECTION-TYPE components: we've
263 ;;; flattened everything into a single INTERSECTION-TYPE object.
264 ;;; 3. There are never any UNION-TYPE components. Either we should
265 ;;; use the distributive rule to rearrange things so that
266 ;;; unions contain intersections and not vice versa, or we
267 ;;; should just punt to using a HAIRY-TYPE.
268 (defstruct (intersection-type (:include compound-type
269 (class-info (type-class-or-lose
271 (:constructor %make-intersection-type
275 ;;; Return TYPE converted to canonical form for a situation where the
276 ;;; "type" '* (which SBCL still represents as a type even though ANSI
277 ;;; CL defines it as a related but different kind of placeholder) is
278 ;;; equivalent to type T.
279 (defun type-*-to-t
(type)
280 (if (type= type
*wild-type
*)
284 ;;; A CONS-TYPE is used to represent a CONS type.
285 (defstruct (cons-type (:include ctype
(class-info (type-class-or-lose 'cons
)))
287 ;; ANSI says that for CAR and CDR subtype
288 ;; specifiers '* is equivalent to T. In order
289 ;; to avoid special cases in SUBTYPEP and
290 ;; possibly elsewhere, we slam all CONS-TYPE
291 ;; objects into canonical form w.r.t. this
292 ;; equivalence at creation time.
293 make-cons-type
(car-raw-type
296 (car-type (type-*-to-t car-raw-type
))
297 (cdr-type (type-*-to-t cdr-raw-type
))))
299 ;; the CAR and CDR element types (to support ANSI (CONS FOO BAR) types)
301 ;; FIXME: Most or all other type structure slots could also be :READ-ONLY.
302 (car-type (missing-arg) :type ctype
:read-only t
)
303 (cdr-type (missing-arg) :type ctype
:read-only t
))
307 ;;; Return the type structure corresponding to a type specifier. We
308 ;;; pick off structure types as a special case.
310 ;;; Note: VALUES-SPECIFIER-TYPE-CACHE-CLEAR must be called whenever a
311 ;;; type is defined (or redefined).
312 (defun-cached (values-specifier-type
313 :hash-function
(lambda (x)
314 (logand (sxhash x
) #x3FF
))
316 :init-wrapper
!cold-init-forms
)
318 (let ((u (uncross orig
)))
319 (or (info :type
:builtin u
)
320 (let ((spec (type-expand u
)))
322 ((and (not (eq spec u
))
323 (info :type
:builtin spec
)))
324 ((eq (info :type
:kind spec
) :instance
)
325 (sb!xc
:find-class spec
))
327 ;; There doesn't seem to be any way to translate
328 ;; (TYPEP SPEC 'BUILT-IN-CLASS) into something which can be
329 ;; executed on the host Common Lisp at cross-compilation time.
331 "stub: (TYPEP SPEC 'BUILT-IN-CLASS) on xc host")
332 (if (typep spec
'built-in-class
)
333 (or (built-in-class-translation spec
) spec
)
336 (let* (;; FIXME: This automatic promotion of FOO-style
337 ;; specs to (FOO)-style specs violates the ANSI
338 ;; standard. Unfortunately, we can't fix the
339 ;; problem just by removing it, since then things
340 ;; downstream should break. But at some point we
341 ;; should fix this and the things downstream too.
342 (lspec (if (atom spec
) (list spec
) spec
))
343 (fun (info :type
:translator
(car lspec
))))
346 ((or (and (consp spec
) (symbolp (car spec
)))
348 (when (and *type-system-initialized
*
349 (not (eq (info :type
:kind spec
)
350 :forthcoming-defclass-type
)))
351 (signal 'parse-unknown-type
:specifier spec
))
352 ;; (The RETURN-FROM here inhibits caching.)
353 (return-from values-specifier-type
354 (make-unknown-type :specifier spec
)))
356 (error "bad thing to be a type specifier: ~S"
359 ;;; This is like VALUES-SPECIFIER-TYPE, except that we guarantee to
360 ;;; never return a VALUES type.
361 (defun specifier-type (x)
362 (let ((res (values-specifier-type x
)))
363 (when (values-type-p res
)
364 (error "VALUES type illegal in this context:~% ~S" x
))
367 (defun single-value-specifier-type (x)
368 (let ((res (specifier-type x
)))
369 (if (eq res
*wild-type
*)
373 ;;; Similar to MACROEXPAND, but expands DEFTYPEs. We don't bother
374 ;;; returning a second value.
375 (defun type-expand (form)
376 (let ((def (cond ((symbolp form
)
377 (info :type
:expander form
))
378 ((and (consp form
) (symbolp (car form
)))
379 (info :type
:expander
(car form
)))
382 (type-expand (funcall def
(if (consp form
) form
(list form
))))
385 ;;; Note that the type NAME has been (re)defined, updating the
386 ;;; undefined warnings and VALUES-SPECIFIER-TYPE cache.
387 (defun %note-type-defined
(name)
388 (declare (symbol name
))
389 (note-name-defined name
:type
)
390 (when (boundp 'sb
!kernel
::*values-specifier-type-cache-vector
*)
391 (values-specifier-type-cache-clear))
394 (!defun-from-collected-cold-init-forms
!early-type-cold-init
)