0.6.11.10:
[sbcl.git] / src / code / early-type.lisp
1 ;;;; This software is part of the SBCL system. See the README file for
2 ;;;; more information.
3 ;;;;
4 ;;;; This software is derived from the CMU CL system, which was
5 ;;;; written at Carnegie Mellon University and released into the
6 ;;;; public domain. The software is in the public domain and is
7 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
8 ;;;; files for more information.
9
10 (in-package "SB!KERNEL")
11
12 (!begin-collecting-cold-init-forms)
13
14 ;;; Has the type system been properly initialized? (I.e. is it OK to
15 ;;; use it?)
16 (defvar *type-system-initialized* #+sb-xc-host nil) ; (set in cold load)
17 \f
18 ;;; Return the type structure corresponding to a type specifier. We
19 ;;; pick off structure types as a special case.
20 ;;;
21 ;;; Note: VALUES-SPECIFIER-TYPE-CACHE-CLEAR must be called whenever a
22 ;;; type is defined (or redefined).
23 (defun-cached (values-specifier-type
24                :hash-function (lambda (x)
25                                 ;; FIXME: the THE FIXNUM stuff is
26                                 ;; redundant in SBCL (or modern CMU
27                                 ;; CL) because of type inference.
28                                 (the fixnum
29                                      (logand (the fixnum (sxhash x))
30                                              #x3FF)))
31                :hash-bits 10
32                :init-wrapper !cold-init-forms)
33               ((orig eq))
34   (let ((u (uncross orig)))
35     (or (info :type :builtin u)
36         (let ((spec (type-expand u)))
37           (cond
38            ((and (not (eq spec u))
39                  (info :type :builtin spec)))
40            ((eq (info :type :kind spec) :instance)
41             (sb!xc:find-class spec))
42            ((typep spec 'class)
43             ;; There doesn't seem to be any way to translate
44             ;; (TYPEP SPEC 'BUILT-IN-CLASS) into something which can be
45             ;; executed on the host Common Lisp at cross-compilation time.
46             #+sb-xc-host (error
47                           "stub: (TYPEP SPEC 'BUILT-IN-CLASS) on xc host")
48             (if (typep spec 'built-in-class)
49                 (or (built-in-class-translation spec) spec)
50                 spec))
51            (t
52             (let* (;; FIXME: This 
53                    (lspec (if (atom spec) (list spec) spec))
54                    (fun (info :type :translator (car lspec))))
55               (cond (fun (funcall fun lspec))
56                     ((or (and (consp spec) (symbolp (car spec)))
57                          (symbolp spec))
58                      (when *type-system-initialized*
59                        (signal 'parse-unknown-type :specifier spec))
60                      ;; (The RETURN-FROM here inhibits caching.)
61                      (return-from values-specifier-type
62                        (make-unknown-type :specifier spec)))
63                     (t
64                      (error "bad thing to be a type specifier: ~S"
65                             spec))))))))))
66
67 ;;; Like VALUES-SPECIFIER-TYPE, except that we guarantee to never
68 ;;; return a VALUES type.
69 (defun specifier-type (x)
70   (let ((res (values-specifier-type x)))
71     (when (values-type-p res)
72       (error "VALUES type illegal in this context:~%  ~S" x))
73     res))
74
75 ;;; Similar to MACROEXPAND, but expands DEFTYPEs. We don't bother
76 ;;; returning a second value.
77 (defun type-expand (form)
78   (let ((def (cond ((symbolp form)
79                     (info :type :expander form))
80                    ((and (consp form) (symbolp (car form)))
81                     (info :type :expander (car form)))
82                    (t nil))))
83     (if def
84         (type-expand (funcall def (if (consp form) form (list form))))
85         form)))
86
87 ;;; A HAIRY-TYPE represents anything too weird to be described
88 ;;; reasonably or to be useful, such as NOT, SATISFIES, unknown types,
89 ;;; and unreasonably complicated types involving AND. We just remember
90 ;;; the original type spec.
91 (defstruct (hairy-type (:include ctype
92                                  (class-info (type-class-or-lose 'hairy))
93                                  (enumerable t))
94                        (:copier nil)
95                        #!+cmu (:pure nil))
96   ;; the Common Lisp type-specifier
97   (specifier nil :type t))
98
99 (!define-type-class hairy)
100
101 ;;; An UNKNOWN-TYPE is a type not known to the type system (not yet
102 ;;; defined). We make this distinction since we don't want to complain
103 ;;; about types that are hairy but defined.
104 (defstruct (unknown-type (:include hairy-type)
105                          (:copier nil)))
106
107 ;;; ARGS-TYPE objects are used both to represent VALUES types and
108 ;;; to represent FUNCTION types.
109 (defstruct (args-type (:include ctype)
110                       (:constructor nil)
111                       (:copier nil))
112   ;; Lists of the type for each required and optional argument.
113   (required nil :type list)
114   (optional nil :type list)
115   ;; The type for the rest arg. NIL if there is no rest arg.
116   (rest nil :type (or ctype null))
117   ;; True if keyword arguments are specified.
118   (keyp nil :type boolean)
119   ;; List of key-info structures describing the keyword arguments.
120   (keywords nil :type list)
121   ;; True if other keywords are allowed.
122   (allowp nil :type boolean))
123
124 (defstruct (values-type
125             (:include args-type
126                       (class-info (type-class-or-lose 'values)))
127             (:copier nil)))
128
129 (!define-type-class values)
130
131 (defstruct (function-type
132             (:include args-type
133                       (class-info (type-class-or-lose 'function))))
134   ;; True if the arguments are unrestrictive, i.e. *.
135   (wild-args nil :type boolean)
136   ;; Type describing the return values. This is a values type
137   ;; when multiple values were specified for the return.
138   (returns (required-argument) :type ctype))
139
140 ;;; The CONSTANT-TYPE structure represents a use of the
141 ;;; CONSTANT-ARGUMENT "type specifier", which is only meaningful in
142 ;;; function argument type specifiers used within the compiler. (It
143 ;;; represents something that the compiler knows to be a constant.)
144 (defstruct (constant-type
145             (:include ctype
146                       (class-info (type-class-or-lose 'constant)))
147             (:copier nil))
148   ;; The type which the argument must be a constant instance of for this type
149   ;; specifier to win.
150   (type (required-argument) :type ctype))
151
152 ;;; The NAMED-TYPE is used to represent *, T and NIL. These types must be
153 ;;; super- or sub-types of all types, not just classes and * and NIL aren't
154 ;;; classes anyway, so it wouldn't make much sense to make them built-in
155 ;;; classes.
156 (defstruct (named-type (:include ctype
157                                  (class-info (type-class-or-lose 'named)))
158                        (:copier nil))
159   (name nil :type symbol))
160
161 ;;; A NUMERIC-TYPE represents any numeric type, including things
162 ;;; such as FIXNUM.
163 (defstruct (numeric-type (:include ctype
164                                    (class-info (type-class-or-lose
165                                                 'number)))
166                          #!+negative-zero-is-not-zero
167                          (:constructor %make-numeric-type))
168   ;; The kind of numeric type we have. NIL if not specified (just NUMBER or
169   ;; COMPLEX).
170   ;;
171   ;; KLUDGE: A slot named CLASS for a non-CLASS value is bad.
172   ;; Especially when a CLASS value *is* stored in another slot (called
173   ;; CLASS-INFO:-). Perhaps this should be called CLASS-NAME? Also
174   ;; weird that comment above says "Numeric-Type is used to represent
175   ;; all numeric types" but this slot doesn't allow COMPLEX as an
176   ;; option.. how does this fall into "not specified" NIL case above?
177   (class nil :type (member integer rational float nil))
178   ;; Format for a float type. NIL if not specified or not a float. Formats
179   ;; which don't exist in a given implementation don't appear here.
180   (format nil :type (or float-format null))
181   ;; Is this a complex numeric type?  Null if unknown (only in NUMBER.)
182   ;;
183   ;; FIXME: I'm bewildered by FOO-P names for things not intended to
184   ;; interpreted as truth values. Perhaps rename this COMPLEXNESS?
185   (complexp :real :type (member :real :complex nil))
186   ;; The upper and lower bounds on the value, or NIL if there is no
187   ;; bound. If a list of a number, the bound is exclusive. Integer
188   ;; types never have exclusive bounds.
189   (low nil :type (or number cons null))
190   (high nil :type (or number cons null)))
191
192 ;;; The Array-Type is used to represent all array types, including
193 ;;; things such as SIMPLE-STRING.
194 (defstruct (array-type (:include ctype
195                                  (class-info (type-class-or-lose 'array)))
196                        (:copier nil))
197   ;; the dimensions of the array, or * if unspecified. If a dimension
198   ;; is unspecified, it is *.
199   (dimensions '* :type (or list (member *)))
200   ;; Is this not a simple array type? (:MAYBE means that we don't know.)
201   (complexp :maybe :type (member t nil :maybe))
202   ;; the element type as originally specified
203   (element-type (required-argument) :type ctype)
204   ;; the element type as it is specialized in this implementation
205   (specialized-element-type *wild-type* :type ctype))
206
207 ;;; A MEMBER-TYPE represent a use of the MEMBER type specifier. We
208 ;;; bother with this at this level because MEMBER types are fairly
209 ;;; important and union and intersection are well defined.
210 (defstruct (member-type (:include ctype
211                                   (class-info (type-class-or-lose 'member))
212                                   (enumerable t))
213                         (:copier nil)
214                         #-sb-xc-host (:pure nil))
215   ;; the things in the set, with no duplications
216   (members nil :type list))
217
218 ;;; A COMPOUND-TYPE is a type defined out of a set of types, 
219 ;;; the common parent of UNION-TYPE and INTERSECTION-TYPE.
220 (defstruct (compound-type (:include ctype)
221                           (:constructor nil)
222                           (:copier nil))
223   (types nil :type list :read-only t))
224
225 ;;; A UNION-TYPE represents a use of the OR type specifier which can't
226 ;;; be canonicalized to something simpler. Canonical form:
227 ;;;   1. There is never more than one MEMBER-TYPE component.
228 ;;;   2. There are never any UNION-TYPE components.
229 (defstruct (union-type (:include compound-type
230                                  (class-info (type-class-or-lose 'union)))
231                        (:constructor %make-union-type (enumerable types))
232                        (:copier nil)))
233
234 ;;; An INTERSECTION-TYPE represents a use of the AND type specifier
235 ;;; which can't be canonicalized to something simpler. Canonical form:
236 ;;;   1. There is never more than one MEMBER-TYPE component.
237 ;;;   2. There are never any INTERSECTION-TYPE or UNION-TYPE components.
238 (defstruct (intersection-type (:include compound-type
239                                         (class-info (type-class-or-lose
240                                                      'intersection)))
241                               (:constructor %make-intersection-type
242                                             (enumerable types))
243                               (:copier nil)))
244
245 ;;; Return TYPE converted to canonical form for a situation where the
246 ;;; "type" '* (which SBCL still represents as a type even though ANSI
247 ;;; CL defines it as a related but different kind of placeholder) is
248 ;;; equivalent to type T.
249 (defun type-*-to-t (type)
250   (if (type= type *wild-type*)
251       *universal-type*
252       type))
253
254 ;;; A CONS-TYPE is used to represent a CONS type.
255 (defstruct (cons-type (:include ctype
256                                 (:class-info (type-class-or-lose 'cons)))
257                       (:constructor
258                        ;; ANSI says that for CAR and CDR subtype
259                        ;; specifiers '* is equivalent to T. In order
260                        ;; to avoid special cases in SUBTYPEP and
261                        ;; possibly elsewhere, we slam all CONS-TYPE
262                        ;; objects into canonical form w.r.t. this
263                        ;; equivalence at creation time.
264                        make-cons-type (car-raw-type
265                                        cdr-raw-type
266                                        &aux
267                                        (car-type (type-*-to-t car-raw-type))
268                                        (cdr-type (type-*-to-t cdr-raw-type))))
269                       (:copier nil))
270   ;; the CAR and CDR element types (to support ANSI (CONS FOO BAR) types)
271   ;;
272   ;; FIXME: Most or all other type structure slots could also be :READ-ONLY.
273   (car-type (required-argument) :type ctype :read-only t)
274   (cdr-type (required-argument) :type ctype :read-only t))
275
276 ;;; Note that the type NAME has been (re)defined, updating the
277 ;;; undefined warnings and VALUES-SPECIFIER-TYPE cache.
278 (defun %note-type-defined (name)
279   (declare (symbol name))
280   (note-name-defined name :type)
281   (when (boundp 'sb!kernel::*values-specifier-type-cache-vector*)
282     (values-specifier-type-cache-clear))
283   (values))
284
285 ;;; Is X a fixnum in the target Lisp?
286 ;;;
287 ;;; KLUDGE: not clear this really belongs in early-type.lisp, but where?
288 (defun target-fixnump (x)
289   (and (integerp x)
290        (<= sb!vm:*target-most-negative-fixnum*
291            x
292            sb!vm:*target-most-positive-fixnum*)))
293
294 (!defun-from-collected-cold-init-forms !early-type-cold-init)