Optimize out-of-line string CONCATENATE, part 2.
[sbcl.git] / src / code / type-class.lisp
blobe02b8bf1138d229885b65b14698cb8964e65cb87
1 ;;;; This file contains the definition of the CTYPE (Compiler TYPE)
2 ;;;; structure, as well as the TYPE-CLASS structure which is a metaobject
3 ;;;; that factors out commonality amongst the subtypes of CTYPE.
4 ;;;; Together they form a sort of mini object system with slightly
5 ;;;; odd dispatching rules. The TYPE-CLASS is a vtable, essentially.
6 ;;;; Various macros related to manipulating those things are here too.
8 ;;;; This software is part of the SBCL system. See the README file for
9 ;;;; more information.
10 ;;;;
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 (!begin-collecting-cold-init-forms)
21 ;; We can't make an instance of any CTYPE descendant until its type-class
22 ;; exists in *TYPE-CLASSES* and the quasi-random state has been made.
23 ;; By initializing the state and type-class storage vector at once,
24 ;; it is obvious that either both have been made or neither one has been.
25 #-sb-xc
26 (progn (defvar *ctype-lcg-state* 1)
27 (defvar *ctype-hash-state* (make-random-state))
28 (defvar *type-classes* (make-array 20 :fill-pointer 0)))
29 #+sb-xc
30 (macrolet ((def ()
31 (let* ((state-type `(unsigned-byte ,sb!vm:n-positive-fixnum-bits))
32 (initform `(make-array 1 :element-type ',state-type))
33 (n (length *type-classes*)))
34 `(progn
35 (declaim (type (simple-array ,state-type (1))
36 *ctype-hash-state*)
37 (type (simple-vector ,n) *type-classes*))
38 ;; The value forms are for type-correctness only.
39 ;; COLD-INIT-FORMS will already have been run.
40 (defglobal *ctype-hash-state* ,initform)
41 (defglobal *type-classes* (make-array ,n))
42 (!cold-init-forms (setq *ctype-hash-state* ,initform))))))
43 (def))
45 (defun type-class-or-lose (name)
46 (or (find name *type-classes* :key #'type-class-name)
47 (error "~S is not a defined type class." name)))
49 #-sb-xc-host
50 (define-compiler-macro type-class-or-lose (&whole form name)
51 ;; If NAME is a quoted constant, the resultant form should be
52 ;; a fixed index into *TYPE-CLASSES* except that during the building
53 ;; of the cross-compiler the array hasn't been populated yet.
54 ;; One solution to that, which I favored, is that DEFINE-TYPE-CLASS
55 ;; appear before the structure definition that uses the corresponding
56 ;; type-class in its slot initializer. That posed a problem for
57 ;; the :INHERITS option, because the constructor of a descendant
58 ;; grabs all the methods [sic] from its ancestor at the time the
59 ;; descendant is defined, which means the methods of the ancestor
60 ;; should have been filled in, which means at least one DEFINE-TYPE-CLASS
61 ;; wants to appear _after_ a structure definition that uses it.
62 (if (constantp name)
63 (let ((name (constant-form-value name)))
64 `(aref *type-classes*
65 ,(or (position name *type-classes* :key #'type-class-name)
66 (error "~S is not a defined type class." name))))
67 form))
69 (defun must-supply-this (&rest foo)
70 (/show0 "failing in MUST-SUPPLY-THIS")
71 (error "missing type method for ~S" foo))
73 ;;; A TYPE-CLASS object represents the "kind" of a type. It mainly
74 ;;; contains functions which are methods on that kind of type, but is
75 ;;; also used in EQ comparisons to determined if two types have the
76 ;;; "same kind".
77 (def!struct (type-class
78 #-no-ansi-print-object
79 (:print-object (lambda (x stream)
80 (print-unreadable-object (x stream :type t)
81 (prin1 (type-class-name x) stream)))))
82 ;; the name of this type class (used to resolve references at load time)
83 (name (missing-arg) :type symbol :read-only t)
84 ;; Dyadic type methods. If the classes of the two types are EQ, then
85 ;; we call the SIMPLE-xxx method. If the classes are not EQ, and
86 ;; either type's class has a COMPLEX-xxx method, then we call it.
88 ;; Although it is undefined which method will get precedence when
89 ;; both types have a complex method, the complex method can assume
90 ;; that the second arg always is in its class, and the first always
91 ;; is not. The arguments to commutative operations will be swapped
92 ;; if the first argument has a complex method.
94 ;; Since SUBTYPEP is not commutative, we have two complex methods.
95 ;; The ARG1 method is only called when the first argument is in its
96 ;; class, and the ARG2 method is only called when called when the
97 ;; second type is. If either is specified, both must be.
98 ;; FIXME: "both must be" is false of CLASSOID type-class.
99 ;; Figure out if this is a comment bug or a logic bug.
100 ;; * (type-class-complex-subtypep-arg1 (type-class-or-lose 'classoid)) => NIL
101 ;; * (type-class-complex-subtypep-arg2 (type-class-or-lose 'classoid))
102 ;; => #<FUNCTION CLASSOID-COMPLEX-SUBTYPEP-ARG2-TYPE-METHOD>
103 (simple-subtypep #'must-supply-this :type function)
104 (complex-subtypep-arg1 nil :type (or function null))
105 (complex-subtypep-arg2 nil :type (or function null))
106 ;; SIMPLE-UNION2, COMPLEX-UNION2, SIMPLE-INTERSECTION2, and
107 ;; COMPLEX-INTERSECTION2 methods take pairs of types and try to find
108 ;; a new type which expresses the result nicely, better than could
109 ;; be done by just stuffing the two component types into an
110 ;; UNION-TYPE or INTERSECTION-TYPE object. They return NIL on
111 ;; failure, or a CTYPE for success.
113 ;; Note: These methods are similar to CMU CL's SIMPLE-UNION,
114 ;; COMPLEX-UNION, SIMPLE-INTERSECTION, and COMPLEX-UNION methods.
115 ;; They were reworked in SBCL because SBCL has INTERSECTION-TYPE
116 ;; objects (where CMU CL just punted to HAIRY-TYPE) and because SBCL
117 ;; wants to simplify unions and intersections by considering all
118 ;; possible pairwise simplifications (where the CMU CL code only
119 ;; considered simplifications between types which happened to appear
120 ;; next to each other the argument sequence).
122 ;; Differences in detail from old CMU CL methods:
123 ;; * SBCL's methods are more parallel between union and
124 ;; intersection forms. Each returns one values, (OR NULL CTYPE).
125 ;; * SBCL doesn't use type methods to deal with unions or
126 ;; intersections of the COMPOUND-TYPE of the corresponding form.
127 ;; Instead the wrapper functions TYPE-UNION2, TYPE-INTERSECTION2,
128 ;; TYPE-UNION, and TYPE-INTERSECTION handle those cases specially
129 ;; (and deal with canonicalization/simplification issues at the
130 ;; same time).
131 (simple-union2 #'hierarchical-union2 :type function)
132 (complex-union2 nil :type (or function null))
133 (simple-intersection2 #'hierarchical-intersection2 :type function)
134 (complex-intersection2 nil :type (or function null))
135 (simple-= #'must-supply-this :type function)
136 (complex-= nil :type (or function null))
137 ;; monadic functions
138 (negate #'must-supply-this :type function)
139 ;; a function which returns a Common Lisp type specifier
140 ;; representing this type
141 (unparse #'must-supply-this :type function)
143 ;; Can types of this type-class contain other types?
144 ;; A global property of our
145 ;; implementation (which unfortunately seems impossible to enforce
146 ;; with assertions or other in-the-code checks and constraints) is
147 ;; that subclasses which don't contain other types correspond to
148 ;; disjoint subsets (except of course for the NAMED-TYPE T, which
149 ;; covers everything). So NUMBER-TYPE is disjoint from CONS-TYPE is
150 ;; is disjoint from MEMBER-TYPE and so forth. But types which can
151 ;; contain other types, like HAIRY-TYPE and INTERSECTION-TYPE, can
152 ;; violate this rule.
153 (might-contain-other-types-p nil :type boolean :read-only t)
154 ;; a function which returns T if the CTYPE could possibly be
155 ;; equivalent to a MEMBER type. If not a function, then it's
156 ;; a constant T or NIL for all instances of this type class.
157 ;; Note that the old comment for this slot was
158 ;; "True if this type has a fixed number of members, and as such
159 ;; could possibly be completely specified in a MEMBER type."
160 ;; The second half of that is right because of the "possibly,"
161 ;; but "has a fixed number" is too strong a claim, because we
162 ;; set enumerable=T for NEGATION and HAIRY and some other things.
163 ;; Conceptually the choices are really {yes, no, unknown}, but
164 ;; whereas "no" means "definitely not", T means "yes or maybe".
165 (enumerable-p nil :type (or function boolean) :read-only t)
166 ;; a function which returns T if the CTYPE is inhabited by a single
167 ;; object and, as a value, the object. Otherwise, returns NIL, NIL.
168 ;; The default case (NIL) is interpreted as a function that always
169 ;; returns NIL, NIL.
170 (singleton-p nil :type (or function null))
173 Not used, and not really right. Probably we want a TYPE= alist for the
174 unary operations, since there are lots of interesting unary predicates that
175 aren't equivalent to an entire class
176 ;; Names of functions used for testing the type of objects in this type
177 ;; class. UNARY-PREDICATE takes just the object, whereas PREDICATE gets
178 ;; passed both the object and the CTYPE. Normally one or the other will be
179 ;; supplied for any type that can be passed to TYPEP; there is no point in
180 ;; supplying both.
181 (unary-typep nil :type (or symbol null))
182 (typep nil :type (or symbol null))
183 ;; These are like TYPEP and UNARY-TYPEP except they coerce objects to
184 ;; the type.
185 (unary-coerce nil :type (or symbol null))
186 (coerce :type (or symbol null))
189 #!-sb-fluid (declaim (freeze-type type-class))
191 #+sb-xc-host
192 (defun ctype-random (mask)
193 (logand (setq *ctype-lcg-state*
194 (logand #x8fffff (+ (* 1103515245 *ctype-lcg-state*) 12345)))
195 mask))
197 ;;; the base class for the internal representation of types
199 ;; Each CTYPE instance (incl. subtypes thereof) has a random opaque hash value.
200 ;; Hashes are mixed together to form a lookup key in the memoization wrappers
201 ;; for most operations in CTYPES. This works because CTYPEs are immutable.
202 ;; But some bits are "stolen" from the hash as flag bits.
203 ;; The sign bit indicates that the object is the *only* object representing
204 ;; its type-specifier - it is an "interned" object.
205 ;; The next highest bit indicates that the object, if compared for TYPE=
206 ;; against an interned object can quickly return false when not EQ.
207 ;; Complicated types don't admit the quick failure check.
208 ;; At any rate, the totally opaque pseudo-random bits are under this mask.
209 (defconstant +ctype-hash-mask+
210 (ldb (byte (1- sb!vm:n-positive-fixnum-bits) 0) -1))
212 ;;; When comparing two ctypes, if this bit is 1 in each and they are not EQ,
213 ;;; and at least one is interned, then they are not TYPE=.
214 (defconstant +type-admits-type=-optimization+
215 (ash 1 (- sb!vm:n-positive-fixnum-bits 1)))
217 ;;; Represent an index into *SPECIALIZED-ARRAY-ELEMENT-TYPE-PROPERTIES*
218 ;;; if applicable. For types which are not array specializations,
219 ;;; the bits are arbitrary.
220 (defmacro !ctype-saetp-index (x)
221 `(ldb (byte 5 ,(- sb!vm:n-positive-fixnum-bits 6)) (type-hash-value ,x)))
223 (def!struct (ctype (:conc-name type-)
224 (:constructor nil)
225 (:make-load-form-fun make-type-load-form)
226 #-sb-xc-host (:pure t))
227 ;; the class of this type
229 ;; FIXME: It's unnecessarily confusing to have a structure accessor
230 ;; named TYPE-CLASS-INFO which is an accessor for the CTYPE structure
231 ;; even though the TYPE-CLASS structure also exists in the system.
232 ;; Rename this slot: TYPE-CLASS or ASSOCIATED-TYPE-CLASS or something.
233 ;; [or TYPE-VTABLE or TYPE-METHODS either of which basically equates
234 ;; a type-class with the set of things it can do, while avoiding
235 ;; ambiguity to whether it is a 'CLASS-INFO' slot in a 'TYPE'
236 ;; or an 'INFO' slot in a 'TYPE-CLASS']
237 (class-info (missing-arg) :type type-class)
238 ;; an arbitrary hash code used in EQ-style hashing of identity
239 ;; (since EQ hashing can't be done portably)
240 ;; - in the host lisp, generate a hash value using a known, simple
241 ;; random number generator (rather than the host lisp's
242 ;; implementation of RANDOM)
243 ;; - in the target, use scrambled bits from the allocation pointer
244 ;; instead.
245 (hash-value
246 #+sb-xc-host (ctype-random +ctype-hash-mask+)
247 #-sb-xc-host (sb!impl::quasi-random-address-based-hash
248 *ctype-hash-state* +ctype-hash-mask+)
249 :type (signed-byte #.sb!vm:n-fixnum-bits)
250 ;; FIXME: is there a better way to initialize the hash value
251 ;; and its flag bit simultaneously rather than have it
252 ;; be a read/write slot?
253 :read-only nil))
255 ;;; The "interned" bit indicates uniqueness of the internal representation of
256 ;;; any specifier that parses to this object.
257 ;;; Not all interned types admit TYPE= optimization. As one example:
258 ;;; (type= (specifier-type '(array (unsigned-byte 6) (*)))
259 ;;; (specifier-type '(array (unsigned-byte 7) (*)))) => T and T
260 ;;; because we preserve the difference in spelling of the two types.
261 (defun mark-ctype-interned (obj)
262 (setf (type-hash-value obj)
263 (logior sb!xc:most-negative-fixnum
264 (if (eq (type-class-name (type-class-info obj)) 'array)
266 +type-admits-type=-optimization+)
267 (type-hash-value obj)))
268 obj)
270 ;; For cold-init: improve the randomness of the hash.
271 ;; (The host uses at most 21 bits of randomness. See CTYPE-RANDOM)
272 #+sb-xc
273 (defun !fix-ctype-hash (obj)
274 (let ((saetp-index (!ctype-saetp-index obj)))
275 ;; Preserve the interned-p and type=-optimization bits
276 ;; by flipping only the bits under the hash-mask.
277 (setf (type-hash-value obj)
278 (logxor (logand (sb!impl::quasi-random-address-based-hash
279 *ctype-hash-state* +ctype-hash-mask+))
280 (type-hash-value obj)))
281 ;; Except that some of those "non-intelligent" bits contain
282 ;; critical information, if this type is an array specialization.
283 (setf (!ctype-saetp-index obj) saetp-index))
284 obj)
286 (declaim (inline type-might-contain-other-types-p))
287 (defun type-might-contain-other-types-p (ctype)
288 (type-class-might-contain-other-types-p (type-class-info ctype)))
290 (declaim (inline type-enumerable))
291 (defun type-enumerable (ctype)
292 (let ((answer (type-class-enumerable-p (type-class-info ctype))))
293 (if (functionp answer)
294 (funcall answer ctype)
295 answer)))
297 #+sb-xc
298 (eval-when (:compile-toplevel)
299 (assert (= (length (dd-slots (find-defstruct-description 'type-class)))
300 ;; there exist two boolean slots, plus NAME
301 (+ (length !type-class-fun-slots) 3))))
303 ;; Unfortunately redundant with the slots in the DEF!STRUCT,
304 ;; but allows asserting about correctness of the constructor
305 ;; without relying on introspection in host Lisp.
306 (defconstant-eqx !type-class-fun-slots
307 '(simple-subtypep
308 complex-subtypep-arg1
309 complex-subtypep-arg2
310 simple-union2
311 complex-union2
312 simple-intersection2
313 complex-intersection2
314 simple-=
315 complex-=
316 negate
317 unparse
318 singleton-p)
319 #'equal)
321 (eval-when (#-sb-xc :compile-toplevel :load-toplevel :execute)
322 (defun !type-class-fun-slot (name)
323 (unless (member name !type-class-fun-slots
324 :key (if (keywordp name) 'keywordicate 'identity))
325 (warn "Undefined type-class method ~S" name))
326 (symbolicate "TYPE-CLASS-" name)))
328 (defmacro !define-type-method ((class method &rest more-methods)
329 lambda-list &body body)
330 (let ((name (symbolicate class "-" method "-TYPE-METHOD")))
331 `(progn
332 (defun ,name ,lambda-list
333 ,@body)
334 (!cold-init-forms
335 ,@(mapcar (lambda (method)
336 `(setf (,(!type-class-fun-slot method)
337 (type-class-or-lose ',class))
338 #',name))
339 (cons method more-methods)))
340 ',name)))
342 (defmacro !define-type-class (name &key inherits
343 (enumerable (unless inherits (must-supply-this))
344 enumerable-supplied-p)
345 (might-contain-other-types
346 (unless inherits (must-supply-this))
347 might-contain-other-types-supplied-p))
348 (let ((make-it
349 `(let ,(if inherits `((parent (type-class-or-lose ',inherits))))
350 (make-type-class
351 :name ',name
352 :enumerable-p ,(if enumerable-supplied-p
353 enumerable
354 `(type-class-enumerable-p parent))
355 :might-contain-other-types-p
356 ,(if might-contain-other-types-supplied-p
357 might-contain-other-types
358 `(type-class-might-contain-other-types-p parent))
359 ,@(when inherits
360 (loop for name in !type-class-fun-slots
361 append `(,(keywordicate name)
362 (,(!type-class-fun-slot name) parent))))))))
363 #-sb-xc
364 `(if (find ',name *type-classes* :key #'type-class-name)
365 (warn "Not redefining type-class ~S" ',name)
366 (vector-push-extend ,make-it *type-classes*))
367 ;; The Nth entry in the array of classes contain a list of instances
368 ;; of the type-class created by genesis that need patching.
369 ;; Types are dumped into the cold core without pointing to their class
370 ;; which avoids a bootstrap problem: it's tricky to dump a type-class.
371 #+sb-xc
372 (let ((type-class-index
373 (position name *type-classes* :key #'type-class-name))
374 (slot-index
375 ;; KLUDGE: silence bogus warning that FIND "certainly" returns NIL
376 (locally (declare (notinline find))
377 (dsd-index (find 'class-info
378 (dd-slots (find-defstruct-description 'ctype))
379 :key #'dsd-name)))))
380 `(!cold-init-forms
381 (let* ((backpatch-list (svref *type-classes* ,type-class-index))
382 (type-class ,make-it))
383 (setf (svref *type-classes* ,type-class-index) type-class)
384 #+nil
385 (progn
386 (princ ,(format nil "Patching type-class ~A into instances: " name))
387 (princ (length backpatch-list))
388 (terpri))
389 (dolist (instance backpatch-list)
390 ;; Fixup the class first, in case fixing the hash needs the class.
391 ;; (It doesn't currently, but just in case it does)
392 (setf (%instance-ref instance ,slot-index) type-class)
393 (!fix-ctype-hash instance)))))))
395 ;;; Define the translation from a type-specifier to a type structure for
396 ;;; some particular type. Syntax is identical to DEFTYPE.
397 ;;; Semantics are slightly different though: DEFTYPE causes the default
398 ;;; for missing &OPTIONAL arguments to be '* but a translator requires
399 ;;; an explicit default of '*, or else it assumes a default of NIL.
400 (defmacro !def-type-translator (name &rest stuff)
401 (declare (type symbol name))
402 (let* ((allow-atom (if (eq (car stuff) :list) (progn (pop stuff) nil) t))
403 (lambda-list (pop stuff))
404 (context-var-p (typep (car lambda-list) '(cons (eql :context))))
405 (context
406 (if context-var-p (cadr (pop lambda-list)) (make-symbol "CONTEXT")))
407 ;; If atoms are allowed, then the internal destructuring-bind receives
408 ;; NIL when the spec is an atom; it should not take CDR of its input.
409 ;; (Note that a &WHOLE argument gets NIL, not the atom in that case)
410 ;; If atoms are disallowed, it's basically like a regular macro.
411 (lexpr (make-macro-lambda nil lambda-list stuff nil nil
412 :accessor (if allow-atom 'identity 'cdr)
413 :environment nil))
414 (ll-decl (third lexpr))
415 (defun-name (symbolicate "PARSE-<" name ">")))
416 (aver (and (eq (car ll-decl) 'declare) (caadr ll-decl) 'sb!c::lambda-list))
417 `(progn
418 (defun ,defun-name (,context spec)
419 ,ll-decl
420 ,@(unless context-var-p `((declare (ignore ,context))))
421 ,(if allow-atom
422 `(,lexpr (and (listp spec) (cdr spec)))
423 `(if (listp spec) (,lexpr spec))))
424 (!cold-init-forms
425 (setf (info :type :expander ',name) (list #',defun-name))))))
427 ;;; Invoke a type method on TYPE1 and TYPE2. If the two types have the
428 ;;; same class, invoke the simple method. Otherwise, invoke any
429 ;;; complex method. If there isn't a distinct COMPLEX-ARG1 method,
430 ;;; then swap the arguments when calling TYPE1's method. If no
431 ;;; applicable method, return DEFAULT.
433 ;;; KLUDGE: It might be a lot easier to understand this and the rest
434 ;;; of the type system code if we used CLOS to express it instead of
435 ;;; trying to maintain this squirrely hand-crufted object system.
436 ;;; Unfortunately that'd require reworking PCL bootstrapping so that
437 ;;; all the compilation can get done by the cross-compiler, which I
438 ;;; suspect is hard, so we'll bear with the old system for the time
439 ;;; being. -- WHN 2001-03-11
440 (defmacro !invoke-type-method (simple complex-arg2 type1 type2 &key
441 (default '(values nil t))
442 ; assume complex fn is symmetric
443 ; unless told otherwise.
444 (complex-arg1 complex-arg2 complex-arg1-p))
445 (declare (type keyword simple complex-arg1 complex-arg2))
446 (once-only ((left type1)
447 (right type2))
448 (once-only ((class1 `(type-class-info ,left))
449 (class2 `(type-class-info ,right)))
450 `(if (eq ,class1 ,class2)
451 (funcall (,(!type-class-fun-slot simple) ,class1) ,left ,right)
452 (acond ((,(!type-class-fun-slot complex-arg2) ,class2)
453 (funcall it ,left ,right))
454 ((,(!type-class-fun-slot complex-arg1) ,class1)
455 ;; if COMPLEX-ARG1 method was provided, the method accepts
456 ;; the arguments exactly as given. Otherwise, flip them.
457 (funcall it ,@(if complex-arg1-p
458 `(,left ,right) `(,right ,left))))
459 (t ,default))))))
461 ;;; This is a very specialized implementation of CLOS-style
462 ;;; CALL-NEXT-METHOD within our twisty little type class object
463 ;;; system, which works given that it's called from within a
464 ;;; COMPLEX-SUBTYPEP-ARG2 method. (We're particularly motivated to
465 ;;; implement CALL-NEXT-METHOD in that case, because ANSI imposes some
466 ;;; strict limits on when SUBTYPEP is allowed to return (VALUES NIL NIL),
467 ;;; so instead of just complacently returning (VALUES NIL NIL) from a
468 ;;; COMPLEX-SUBTYPEP-ARG2 method we usually need to CALL-NEXT-METHOD.)
470 ;;; KLUDGE: In CLOS, this could just be CALL-NEXT-METHOD and
471 ;;; everything would Just Work without us having to think about it. In
472 ;;; our goofy type dispatch system, it's messier to express. It's also
473 ;;; more fragile, since (0) there's no check that it's called from
474 ;;; within a COMPLEX-SUBTYPEP-ARG2 method as it should be, and (1) we
475 ;;; rely on our global knowledge that the next (and only) relevant
476 ;;; method is COMPLEX-SUBTYPEP-ARG1, and (2) we rely on our global
477 ;;; knowledge of the appropriate default for the CSUBTYPEP function
478 ;;; when no next method exists. -- WHN 2002-04-07
480 ;;; (We miss CLOS! -- CSR and WHN)
481 (defun invoke-complex-subtypep-arg1-method (type1 type2 &optional subtypep win)
482 (let* ((type-class (type-class-info type1))
483 (method-fun (type-class-complex-subtypep-arg1 type-class)))
484 (if method-fun
485 (funcall (the function method-fun) type1 type2)
486 (values subtypep win))))
488 ;;; KLUDGE: This function is dangerous, as its overuse could easily
489 ;;; cause stack exhaustion through unbounded recursion. We only use
490 ;;; it in one place; maybe it ought not to be a function at all?
491 (defun invoke-complex-=-other-method (type1 type2)
492 (let* ((type-class (type-class-info type1))
493 (method-fun (type-class-complex-= type-class)))
494 (if method-fun
495 (funcall (the function method-fun) type2 type1)
496 (values nil t))))
498 ;;;; miscellany
500 ;;; Hash two things (types) down to a target fixnum. In CMU CL this was an EQ
501 ;;; hash, but since it now needs to run in vanilla ANSI Common Lisp at
502 ;;; cross-compile time, it's now based on the CTYPE-HASH-VALUE field
503 ;;; instead.
505 ;;; FIXME: This was a macro in CMU CL, and is now an INLINE function. Is
506 ;;; it important for it to be INLINE, or could be become an ordinary
507 ;;; function without significant loss? -- WHN 19990413
508 #!-sb-fluid (declaim (inline type-cache-hash))
509 (declaim (ftype (function (ctype ctype) (signed-byte #.sb!vm:n-fixnum-bits))
510 type-cache-hash))
511 (defun type-cache-hash (type1 type2)
512 (logxor (ash (type-hash-value type1) -3) (type-hash-value type2)))
514 #!-sb-fluid (declaim (inline type-list-cache-hash))
515 (declaim (ftype (function (list) (signed-byte #.sb!vm:n-fixnum-bits))
516 type-list-cache-hash))
517 (defun type-list-cache-hash (types)
518 (loop with res of-type (signed-byte #.sb!vm:n-fixnum-bits) = 0
519 for type in types
520 do (setq res (logxor (ash res -1) (type-hash-value type)))
521 finally (return res)))
523 (!defun-from-collected-cold-init-forms !type-class-cold-init)
525 ;;; A few type representations need to be defined slightly earlier than
526 ;;; 'early-type' is compiled, so they're defined here.
528 ;;; The NAMED-TYPE is used to represent *, T and NIL, the standard
529 ;;; special cases, as well as other special cases needed to
530 ;;; interpolate between regions of the type hierarchy, such as
531 ;;; INSTANCE (which corresponds to all those classes with slots which
532 ;;; are not funcallable), FUNCALLABLE-INSTANCE (those classes with
533 ;;; slots which are funcallable) and EXTENDED-SEQUUENCE (non-LIST
534 ;;; non-VECTOR classes which are also sequences). These special cases
535 ;;; are the ones that aren't really discussed by Baker in his
536 ;;; "Decision Procedure for SUBTYPEP" paper.
537 (defstruct (named-type (:include ctype
538 (class-info (type-class-or-lose 'named)))
539 (:copier nil))
540 (name nil :type symbol :read-only t))
542 ;;; A MEMBER-TYPE represent a use of the MEMBER type specifier. We
543 ;;; bother with this at this level because MEMBER types are fairly
544 ;;; important and union and intersection are well defined.
545 (defstruct (member-type (:include ctype
546 (class-info (type-class-or-lose 'member)))
547 (:copier nil)
548 (:constructor %make-member-type (xset fp-zeroes))
549 #-sb-xc-host (:pure nil))
550 (xset nil :type xset :read-only t)
551 (fp-zeroes nil :type list :read-only t))
553 ;;; An ARRAY-TYPE is used to represent any array type, including
554 ;;; things such as SIMPLE-BASE-STRING.
555 (defstruct (array-type (:include ctype
556 (class-info (type-class-or-lose 'array)))
557 (:constructor %make-array-type
558 (dimensions complexp element-type
559 specialized-element-type))
560 (:copier nil))
561 ;; the dimensions of the array, or * if unspecified. If a dimension
562 ;; is unspecified, it is *.
563 (dimensions '* :type (or list (member *)) :read-only t)
564 ;; Is this not a simple array type? (:MAYBE means that we don't know.)
565 (complexp :maybe :type (member t nil :maybe) :read-only t)
566 ;; the element type as originally specified
567 (element-type nil :type ctype :read-only t)
568 ;; the element type as it is specialized in this implementation
569 (specialized-element-type nil :type ctype :read-only t))
571 (defstruct (character-set-type
572 (:include ctype
573 (class-info (type-class-or-lose 'character-set)))
574 (:constructor %make-character-set-type (pairs))
575 (:copier nil))
576 (pairs (missing-arg) :type list :read-only t))
578 ;;; A COMPOUND-TYPE is a type defined out of a set of types, the
579 ;;; common parent of UNION-TYPE and INTERSECTION-TYPE.
580 (defstruct (compound-type (:include ctype)
581 (:constructor nil)
582 (:copier nil))
583 ;; Formerly defined in every CTYPE, but now just in the ones
584 ;; for which enumerability is variable.
585 (enumerable nil :read-only t)
586 (types nil :type list :read-only t))
588 ;;; A UNION-TYPE represents a use of the OR type specifier which we
589 ;;; couldn't canonicalize to something simpler. Canonical form:
590 ;;; 1. All possible pairwise simplifications (using the UNION2 type
591 ;;; methods) have been performed. Thus e.g. there is never more
592 ;;; than one MEMBER-TYPE component. FIXME: As of sbcl-0.6.11.13,
593 ;;; this hadn't been fully implemented yet.
594 ;;; 2. There are never any UNION-TYPE components.
596 ;;; TODO: As STRING is an especially important union type,
597 ;;; it could be interned by canonicalizing its subparts into
598 ;;; ARRAY of {CHARACTER,BASE-CHAR,NIL} in that exact order always.
599 ;;; It will therefore admit quick TYPE=, but not quick failure, since
600 ;;; (type= (specifier-type '(or (simple-array (member #\a) (*))
601 ;;; (simple-array character (*))
602 ;;; (simple-array nil (*))))
603 ;;; (specifier-type 'simple-string)) => T and T
604 ;;; even though (MEMBER #\A) is not TYPE= to BASE-CHAR.
606 (defstruct (union-type (:include compound-type
607 (class-info (type-class-or-lose 'union)))
608 (:constructor make-union-type (enumerable types))
609 (:copier nil)))
611 ;;; An INTERSECTION-TYPE represents a use of the AND type specifier
612 ;;; which we couldn't canonicalize to something simpler. Canonical form:
613 ;;; 1. All possible pairwise simplifications (using the INTERSECTION2
614 ;;; type methods) have been performed. Thus e.g. there is never more
615 ;;; than one MEMBER-TYPE component.
616 ;;; 2. There are never any INTERSECTION-TYPE components: we've
617 ;;; flattened everything into a single INTERSECTION-TYPE object.
618 ;;; 3. There are never any UNION-TYPE components. Either we should
619 ;;; use the distributive rule to rearrange things so that
620 ;;; unions contain intersections and not vice versa, or we
621 ;;; should just punt to using a HAIRY-TYPE.
622 (defstruct (intersection-type (:include compound-type
623 (class-info (type-class-or-lose
624 'intersection)))
625 (:constructor %make-intersection-type
626 (enumerable types))
627 (:copier nil)))
629 ;;; a list of all the float "formats" (i.e. internal representations;
630 ;;; nothing to do with #'FORMAT), in order of decreasing precision
631 (eval-when (:compile-toplevel :load-toplevel :execute)
632 (defparameter *float-formats*
633 '(long-float double-float single-float short-float)))
635 ;;; The type of a float format.
636 (deftype float-format () `(member ,@*float-formats*))
638 ;;; A NUMERIC-TYPE represents any numeric type, including things
639 ;;; such as FIXNUM.
640 (defstruct (numeric-type (:include ctype
641 (class-info (type-class-or-lose 'number)))
642 (:constructor %make-numeric-type)
643 (:copier nil))
644 ;; Formerly defined in every CTYPE, but now just in the ones
645 ;; for which enumerability is variable.
646 (enumerable nil :type boolean :read-only t)
647 ;; the kind of numeric type we have, or NIL if not specified (just
648 ;; NUMBER or COMPLEX)
650 ;; KLUDGE: A slot named CLASS for a non-CLASS value is bad.
651 ;; Especially when a CLASS value *is* stored in another slot (called
652 ;; CLASS-INFO:-). Perhaps this should be called CLASS-NAME? Also
653 ;; weird that comment above says "Numeric-Type is used to represent
654 ;; all numeric types" but this slot doesn't allow COMPLEX as an
655 ;; option.. how does this fall into "not specified" NIL case above?
656 ;; Perhaps someday we can switch to CLOS and make NUMERIC-TYPE
657 ;; be an abstract base class and INTEGER-TYPE, RATIONAL-TYPE, and
658 ;; whatnot be concrete subclasses..
659 (class nil :type (member integer rational float nil) :read-only t)
660 ;; "format" for a float type (i.e. type specifier for a CPU
661 ;; representation of floating point, e.g. 'SINGLE-FLOAT -- nothing
662 ;; to do with #'FORMAT), or NIL if not specified or not a float.
663 ;; Formats which don't exist in a given implementation don't appear
664 ;; here.
665 (format nil :type (or float-format null) :read-only t)
666 ;; Is this a complex numeric type? Null if unknown (only in NUMBER).
668 ;; FIXME: I'm bewildered by FOO-P names for things not intended to
669 ;; interpreted as truth values. Perhaps rename this COMPLEXNESS?
670 (complexp :real :type (member :real :complex nil) :read-only t)
671 ;; The upper and lower bounds on the value, or NIL if there is no
672 ;; bound. If a list of a number, the bound is exclusive. Integer
673 ;; types never have exclusive bounds, i.e. they may have them on
674 ;; input, but they're canonicalized to inclusive bounds before we
675 ;; store them here.
676 (low nil :type (or number cons null) :read-only t)
677 (high nil :type (or number cons null) :read-only t))
679 ;;; A CONS-TYPE is used to represent a CONS type.
680 (defstruct (cons-type (:include ctype (class-info (type-class-or-lose 'cons)))
681 (:constructor
682 %make-cons-type (car-type
683 cdr-type))
684 (:copier nil))
685 ;; the CAR and CDR element types (to support ANSI (CONS FOO BAR) types)
686 (car-type (missing-arg) :type ctype :read-only t)
687 (cdr-type (missing-arg) :type ctype :read-only t))
689 (in-package "SB!ALIEN")
690 (def!struct (alien-type
691 (:make-load-form-fun sb!kernel:just-dump-it-normally)
692 (:constructor make-alien-type
693 (&key class bits alignment
694 &aux (alignment
695 (or alignment (guess-alignment bits))))))
696 (class 'root :type symbol :read-only t)
697 (bits nil :type (or null unsigned-byte))
698 (alignment nil :type (or null unsigned-byte)))
700 (in-package "SB!KERNEL")
701 (defstruct (alien-type-type
702 (:include ctype
703 (class-info (type-class-or-lose 'alien)))
704 (:constructor %make-alien-type-type (alien-type))
705 (:copier nil))
706 (alien-type nil :type alien-type :read-only t))
708 ;;; the description of a &KEY argument
709 (defstruct (key-info #-sb-xc-host (:pure t)
710 (:copier nil))
711 ;; the key (not necessarily a keyword in ANSI Common Lisp)
712 (name (missing-arg) :type symbol :read-only t)
713 ;; the type of the argument value
714 (type (missing-arg) :type ctype :read-only t))
716 ;;; ARGS-TYPE objects are used both to represent VALUES types and
717 ;;; to represent FUNCTION types.
718 (defstruct (args-type (:include ctype)
719 (:constructor nil)
720 (:copier nil))
721 ;; Lists of the type for each required and optional argument.
722 (required nil :type list :read-only t)
723 (optional nil :type list :read-only t)
724 ;; The type for the rest arg. NIL if there is no &REST arg.
725 (rest nil :type (or ctype null) :read-only t)
726 ;; true if &KEY arguments are specified
727 (keyp nil :type boolean :read-only t)
728 ;; list of KEY-INFO structures describing the &KEY arguments
729 (keywords nil :type list :read-only t)
730 ;; true if other &KEY arguments are allowed
731 (allowp nil :type boolean :read-only t))
733 ;;; (SPECIFIER-TYPE 'FUNCTION) and its subtypes
734 (defstruct (fun-type (:include args-type
735 (class-info (type-class-or-lose 'function)))
736 (:constructor
737 %make-fun-type (required optional rest
738 keyp keywords allowp wild-args returns)))
739 ;; true if the arguments are unrestrictive, i.e. *
740 (wild-args nil :type boolean :read-only t)
741 ;; type describing the return values. This is a values type
742 ;; when multiple values were specified for the return.
743 (returns (missing-arg) :type ctype :read-only t))
745 (declaim (ftype (sfunction (ctype ctype) (values t t)) csubtypep))
746 ;;; Look for nice relationships for types that have nice relationships
747 ;;; only when one is a hierarchical subtype of the other.
748 (defun hierarchical-intersection2 (type1 type2)
749 ;; *EMPTY-TYPE* is involved in a dependency cycle: It wants to be a constant
750 ;; instance of NAMED-TYPE. To construct an instance of a type, you need a
751 ;; type-class. A type-class needs to refer to this function, which refers
752 ;; to *EMPTY-TYPE*, which .... etc.
753 ;; In the cross-compiler, it is actually a constant.
754 #+sb-xc-host (declare (special *empty-type*))
755 (multiple-value-bind (subtypep1 win1) (csubtypep type1 type2)
756 (multiple-value-bind (subtypep2 win2) (csubtypep type2 type1)
757 (cond (subtypep1 type1)
758 (subtypep2 type2)
759 ((and win1 win2) *empty-type*)
760 (t nil)))))
762 (defun hierarchical-union2 (type1 type2)
763 (cond ((csubtypep type1 type2) type2)
764 ((csubtypep type2 type1) type1)
765 (t nil)))