0.6.10.6:
[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* ((lspec (if (atom spec) (list spec) spec))
53                    (fun (info :type :translator (car lspec))))
54               (cond (fun (funcall fun lspec))
55                     ((or (and (consp spec) (symbolp (car spec)))
56                          (symbolp spec))
57                      (when *type-system-initialized*
58                        (signal 'parse-unknown-type :specifier spec))
59                      ;; (The RETURN-FROM here inhibits caching.)
60                      (return-from values-specifier-type
61                        (make-unknown-type :specifier spec)))
62                     (t
63                      (error "bad thing to be a type specifier: ~S"
64                             spec))))))))))
65
66 ;;; Like VALUES-SPECIFIER-TYPE, except that we guarantee to never
67 ;;; return a VALUES type.
68 (defun specifier-type (x)
69   (let ((res (values-specifier-type x)))
70     (when (values-type-p res)
71       (error "VALUES type illegal in this context:~%  ~S" x))
72     res))
73
74 ;;; Similar to MACROEXPAND, but expands DEFTYPEs. We don't bother
75 ;;; returning a second value.
76 (defun type-expand (form)
77   (let ((def (cond ((symbolp form)
78                     (info :type :expander form))
79                    ((and (consp form) (symbolp (car form)))
80                     (info :type :expander (car form)))
81                    (t nil))))
82     (if def
83         (type-expand (funcall def (if (consp form) form (list form))))
84         form)))
85
86 ;;; A HAIRY-TYPE represents anything too weird to be described
87 ;;; reasonably or to be useful, such as NOT, SATISFIES, unknown types,
88 ;;; and unreasonably complicated types involving AND. We just remember
89 ;;; the original type spec.
90 (defstruct (hairy-type (:include ctype
91                                  (class-info (type-class-or-lose 'hairy))
92                                  (enumerable t))
93                        #!+cmu (:pure nil))
94   ;; the Common Lisp type-specifier
95   (specifier nil :type t))
96
97 (!define-type-class hairy)
98
99 ;;; An UNKNOWN-TYPE is a type not known to the type system (not yet
100 ;;; defined). We make this distinction since we don't want to complain
101 ;;; about types that are hairy but defined.
102 (defstruct (unknown-type (:include hairy-type)))
103
104 ;;; ARGS-TYPE objects are used both to represent VALUES types and
105 ;;; to represent FUNCTION types.
106 (defstruct (args-type (:include ctype)
107                       (:constructor nil))
108   ;; Lists of the type for each required and optional argument.
109   (required nil :type list)
110   (optional nil :type list)
111   ;; The type for the rest arg. NIL if there is no rest arg.
112   (rest nil :type (or ctype null))
113   ;; True if keyword arguments are specified.
114   (keyp nil :type boolean)
115   ;; List of key-info structures describing the keyword arguments.
116   (keywords nil :type list)
117   ;; True if other keywords are allowed.
118   (allowp nil :type boolean))
119
120 (defstruct (values-type
121             (:include args-type
122                       (class-info (type-class-or-lose 'values)))))
123
124 (!define-type-class values)
125
126 (defstruct (function-type
127             (:include args-type
128                       (class-info (type-class-or-lose 'function))))
129   ;; True if the arguments are unrestrictive, i.e. *.
130   (wild-args nil :type boolean)
131   ;; Type describing the return values. This is a values type
132   ;; when multiple values were specified for the return.
133   (returns (required-argument) :type ctype))
134
135 ;;; The CONSTANT-TYPE structure represents a use of the
136 ;;; CONSTANT-ARGUMENT "type specifier", which is only meaningful in
137 ;;; function argument type specifiers used within the compiler. (It
138 ;;; represents something that the compiler knows to be a constant.)
139 (defstruct (constant-type
140             (:include ctype
141                       (class-info (type-class-or-lose 'constant))))
142   ;; The type which the argument must be a constant instance of for this type
143   ;; specifier to win.
144   (type (required-argument) :type ctype))
145
146 ;;; The NAMED-TYPE is used to represent *, T and NIL. These types must be
147 ;;; super or sub types of all types, not just classes and * & NIL aren't
148 ;;; classes anyway, so it wouldn't make much sense to make them built-in
149 ;;; classes.
150 (defstruct (named-type (:include ctype
151                                  (class-info (type-class-or-lose 'named))))
152   (name nil :type symbol))
153
154 ;;; The Numeric-Type is used to represent all numeric types, including things
155 ;;; such as FIXNUM.
156 (defstruct (numeric-type (:include ctype
157                                    (class-info (type-class-or-lose
158                                                 'number)))
159                          #!+negative-zero-is-not-zero
160                          (:constructor %make-numeric-type))
161   ;; The kind of numeric type we have. NIL if not specified (just NUMBER or
162   ;; COMPLEX).
163   ;;
164   ;; KLUDGE: A slot named CLASS for a non-CLASS value is bad.
165   ;; Especially when a CLASS value *is* stored in another slot (called
166   ;; CLASS-INFO:-). Perhaps this should be called CLASS-NAME? Also
167   ;; weird that comment above says "Numeric-Type is used to represent
168   ;; all numeric types" but this slot doesn't allow COMPLEX as an
169   ;; option.. how does this fall into "not specified" NIL case above?
170   (class nil :type (member integer rational float nil))
171   ;; Format for a float type. NIL if not specified or not a float. Formats
172   ;; which don't exist in a given implementation don't appear here.
173   (format nil :type (or float-format null))
174   ;; Is this a complex numeric type?  Null if unknown (only in NUMBER.)
175   ;;
176   ;; FIXME: I'm bewildered by FOO-P names for things not intended to
177   ;; interpreted as truth values. Perhaps rename this COMPLEXNESS?
178   (complexp :real :type (member :real :complex nil))
179   ;; The upper and lower bounds on the value, or NIL if there is no
180   ;; bound. If a list of a number, the bound is exclusive. Integer
181   ;; types never have exclusive bounds.
182   (low nil :type (or number cons null))
183   (high nil :type (or number cons null)))
184
185 ;;; The Array-Type is used to represent all array types, including
186 ;;; things such as SIMPLE-STRING.
187 (defstruct (array-type (:include ctype
188                                  (class-info (type-class-or-lose 'array))))
189   ;; The dimensions of the array. * if unspecified. If a dimension is
190   ;; unspecified, it is *.
191   (dimensions '* :type (or list (member *)))
192   ;; Is this not a simple array type? (:MAYBE means that we don't know.)
193   (complexp :maybe :type (member t nil :maybe))
194   ;; The element type as originally specified.
195   (element-type (required-argument) :type ctype)
196   ;; The element type as it is specialized in this implementation.
197   (specialized-element-type *wild-type* :type ctype))
198
199 ;;; The Member-Type represents uses of the MEMBER type specifier. We
200 ;;; bother with this at this level because MEMBER types are fairly
201 ;;; important and union and intersection are well defined.
202 (defstruct (member-type (:include ctype
203                                   (class-info (type-class-or-lose 'member))
204                                   (enumerable t))
205                         #-sb-xc-host (:pure nil))
206   ;; The things in the set, with no duplications.
207   (members nil :type list))
208
209 ;;; A UNION-TYPE represents a use of the OR type specifier which can't
210 ;;; be canonicalized to something simpler. Canonical form:
211 ;;;   1. There is never more than one MEMBER-TYPE component.
212 ;;;   2. There are never any UNION-TYPE components.
213 (defstruct (union-type (:include ctype
214                                  (class-info (type-class-or-lose 'union)))
215                        (:constructor %make-union-type (enumerable types)))
216   ;; The types in the union.
217   (types nil :type list))
218
219 ;;; Return TYPE converted to canonical form for a situation where the
220 ;;; type '* is equivalent to type T.
221 (defun type-*-to-t (type)
222   (if (type= type *wild-type*)
223       *universal-type*
224       type))
225
226 ;;; A CONS-TYPE is used to represent a CONS type.
227 (defstruct (cons-type (:include ctype
228                                 (:class-info (type-class-or-lose 'cons)))
229                       (:constructor
230                        ;; ANSI says that for CAR and CDR subtype
231                        ;; specifiers '* is equivalent to T. In order
232                        ;; to avoid special cases in SUBTYPEP and
233                        ;; possibly elsewhere, we slam all CONS-TYPE
234                        ;; objects into canonical form w.r.t. this
235                        ;; equivalence at creation time.
236                        make-cons-type (car-raw-type
237                                        cdr-raw-type
238                                        &aux
239                                        (car-type (type-*-to-t car-raw-type))
240                                        (cdr-type (type-*-to-t cdr-raw-type)))))
241   ;; the CAR and CDR element types (to support ANSI (CONS FOO BAR) types)
242   ;;
243   ;; FIXME: Most or all other type structure slots could also be :READ-ONLY.
244   (car-type (required-argument) :type ctype :read-only t)
245   (cdr-type (required-argument) :type ctype :read-only t))
246
247 ;;; Note that the type NAME has been (re)defined, updating the
248 ;;; undefined warnings and VALUES-SPECIFIER-TYPE cache.
249 (defun %note-type-defined (name)
250   (declare (symbol name))
251   (note-name-defined name :type)
252   (when (boundp 'sb!kernel::*values-specifier-type-cache-vector*)
253     (values-specifier-type-cache-clear))
254   (values))
255
256 ;;; Is X a fixnum in the target Lisp?
257 ;;;
258 ;;; KLUDGE: not clear this really belongs in early-type.lisp, but where?
259 (defun target-fixnump (x)
260   (and (integerp x)
261        (<= sb!vm:*target-most-negative-fixnum*
262            x
263            sb!vm:*target-most-positive-fixnum*)))
264
265 (!defun-from-collected-cold-init-forms !early-type-cold-init)