Fix build with CLL and CLisp hosts
[sbcl.git] / src / code / type-class.lisp
blobc267916245746b9895ce8b49323a3133550f1aae
1 ;;;; stuff related to the TYPE-CLASS structure
3 ;;;; This software is part of the SBCL system. See the README file for
4 ;;;; more information.
5 ;;;;
6 ;;;; This software is derived from the CMU CL system, which was
7 ;;;; written at Carnegie Mellon University and released into the
8 ;;;; public domain. The software is in the public domain and is
9 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
10 ;;;; files for more information.
12 (in-package "SB!KERNEL")
14 (!begin-collecting-cold-init-forms)
16 ;; We can't make an instance of any CTYPE descendant until its type-class
17 ;; exists in *TYPE-CLASSES* and the quasi-random state has been made.
18 ;; By initializing the state and type-class storage vector at once,
19 ;; it is obvious that either both have been made or neither one has been.
20 #-sb-xc
21 (progn (defvar *ctype-lcg-state* 1)
22 (defvar *ctype-hash-state* (make-random-state))
23 (defvar *type-classes* (make-array 20 :fill-pointer 0)))
24 #+sb-xc
25 (macrolet ((def ()
26 (let* ((state-type `(unsigned-byte ,sb!vm:n-positive-fixnum-bits))
27 (initform `(make-array 1 :element-type ',state-type))
28 (n (length *type-classes*)))
29 `(progn
30 (declaim (type (simple-array ,state-type (1))
31 *ctype-hash-state*)
32 (type (simple-vector ,n) *type-classes*))
33 ;; The value forms are for type-correctness only.
34 ;; COLD-INIT-FORMS will already have been run.
35 (defglobal *ctype-hash-state* ,initform)
36 (defglobal *type-classes* (make-array ,n))
37 (!cold-init-forms
38 (setq *ctype-hash-state* ,initform
39 *type-classes* (make-array ,n)))))))
40 (def))
42 (defun type-class-or-lose (name)
43 (or (find name *type-classes* :key #'type-class-name)
44 (error "~S is not a defined type class." name)))
46 #-sb-xc-host
47 (define-compiler-macro type-class-or-lose (&whole form name)
48 ;; If NAME is a quoted constant, the resultant form should be
49 ;; a fixed index into *TYPE-CLASSES* except that during the building
50 ;; of the cross-compiler the array hasn't been populated yet.
51 ;; One solution to that, which I favored, is that DEFINE-TYPE-CLASS
52 ;; appear before the structure definition that uses the corresponding
53 ;; type-class in its slot initializer. That posed a problem for
54 ;; the :INHERITS option, because the constructor of a descendant
55 ;; grabs all the methods [sic] from its ancestor at the time the
56 ;; descendant is defined, which means the methods of the ancestor
57 ;; should have been filled in, which means at least one DEFINE-TYPE-CLASS
58 ;; wants to appear _after_ a structure definition that uses it.
59 (if (constantp name)
60 (let ((name (constant-form-value name)))
61 `(aref *type-classes*
62 ,(or (position name *type-classes* :key #'type-class-name)
63 (error "~S is not a defined type class." name))))
64 form))
66 (defun must-supply-this (&rest foo)
67 (/show0 "failing in MUST-SUPPLY-THIS")
68 (error "missing type method for ~S" foo))
70 ;;; A TYPE-CLASS object represents the "kind" of a type. It mainly
71 ;;; contains functions which are methods on that kind of type, but is
72 ;;; also used in EQ comparisons to determined if two types have the
73 ;;; "same kind".
74 (def!struct (type-class
75 #-no-ansi-print-object
76 (:print-object (lambda (x stream)
77 (print-unreadable-object (x stream :type t)
78 (prin1 (type-class-name x) stream)))))
79 ;; the name of this type class (used to resolve references at load time)
80 (name (missing-arg) :type symbol :read-only t)
81 ;; Dyadic type methods. If the classes of the two types are EQ, then
82 ;; we call the SIMPLE-xxx method. If the classes are not EQ, and
83 ;; either type's class has a COMPLEX-xxx method, then we call it.
85 ;; Although it is undefined which method will get precedence when
86 ;; both types have a complex method, the complex method can assume
87 ;; that the second arg always is in its class, and the first always
88 ;; is not. The arguments to commutative operations will be swapped
89 ;; if the first argument has a complex method.
91 ;; Since SUBTYPEP is not commutative, we have two complex methods.
92 ;; The ARG1 method is only called when the first argument is in its
93 ;; class, and the ARG2 method is only called when called when the
94 ;; second type is. If either is specified, both must be.
95 (simple-subtypep #'must-supply-this :type function)
96 (complex-subtypep-arg1 nil :type (or function null))
97 (complex-subtypep-arg2 nil :type (or function null))
98 ;; SIMPLE-UNION2, COMPLEX-UNION2, SIMPLE-INTERSECTION2, and
99 ;; COMPLEX-INTERSECTION2 methods take pairs of types and try to find
100 ;; a new type which expresses the result nicely, better than could
101 ;; be done by just stuffing the two component types into an
102 ;; UNION-TYPE or INTERSECTION-TYPE object. They return NIL on
103 ;; failure, or a CTYPE for success.
105 ;; Note: These methods are similar to CMU CL's SIMPLE-UNION,
106 ;; COMPLEX-UNION, SIMPLE-INTERSECTION, and COMPLEX-UNION methods.
107 ;; They were reworked in SBCL because SBCL has INTERSECTION-TYPE
108 ;; objects (where CMU CL just punted to HAIRY-TYPE) and because SBCL
109 ;; wants to simplify unions and intersections by considering all
110 ;; possible pairwise simplifications (where the CMU CL code only
111 ;; considered simplifications between types which happened to appear
112 ;; next to each other the argument sequence).
114 ;; Differences in detail from old CMU CL methods:
115 ;; * SBCL's methods are more parallel between union and
116 ;; intersection forms. Each returns one values, (OR NULL CTYPE).
117 ;; * SBCL doesn't use type methods to deal with unions or
118 ;; intersections of the COMPOUND-TYPE of the corresponding form.
119 ;; Instead the wrapper functions TYPE-UNION2, TYPE-INTERSECTION2,
120 ;; TYPE-UNION, and TYPE-INTERSECTION handle those cases specially
121 ;; (and deal with canonicalization/simplification issues at the
122 ;; same time).
123 (simple-union2 #'hierarchical-union2 :type function)
124 (complex-union2 nil :type (or function null))
125 (simple-intersection2 #'hierarchical-intersection2 :type function)
126 (complex-intersection2 nil :type (or function null))
127 (simple-= #'must-supply-this :type function)
128 (complex-= nil :type (or function null))
129 ;; monadic functions
130 (negate #'must-supply-this :type function)
131 ;; a function which returns a Common Lisp type specifier
132 ;; representing this type
133 (unparse #'must-supply-this :type function)
135 ;; Can types of this type-class contain other types?
136 ;; A global property of our
137 ;; implementation (which unfortunately seems impossible to enforce
138 ;; with assertions or other in-the-code checks and constraints) is
139 ;; that subclasses which don't contain other types correspond to
140 ;; disjoint subsets (except of course for the NAMED-TYPE T, which
141 ;; covers everything). So NUMBER-TYPE is disjoint from CONS-TYPE is
142 ;; is disjoint from MEMBER-TYPE and so forth. But types which can
143 ;; contain other types, like HAIRY-TYPE and INTERSECTION-TYPE, can
144 ;; violate this rule.
145 (might-contain-other-types-p nil)
146 ;; a function which returns T if the CTYPE could possibly be
147 ;; equivalent to a MEMBER type. If not a function, then it's
148 ;; a constant T or NIL for all instances of this type class.
149 ;; Note that the old comment for this slot was
150 ;; "True if this type has a fixed number of members, and as such
151 ;; could possibly be completely specified in a MEMBER type."
152 ;; The second half of that is right because of the "possibly,"
153 ;; but "has a fixed number" is too strong a claim, because we
154 ;; set enumerable=T for NEGATION and HAIRY and some other things.
155 ;; Conceptually the choices are really {yes, no, unknown}, but
156 ;; whereas "no" means "definitely not", T means "yes or maybe".
157 (enumerable-p nil :type (or function null t))
158 ;; a function which returns T if the CTYPE is inhabited by a single
159 ;; object and, as a value, the object. Otherwise, returns NIL, NIL.
160 ;; The default case (NIL) is interpreted as a function that always
161 ;; returns NIL, NIL.
162 (singleton-p nil :type (or function null))
165 Not used, and not really right. Probably we want a TYPE= alist for the
166 unary operations, since there are lots of interesting unary predicates that
167 aren't equivalent to an entire class
168 ;; Names of functions used for testing the type of objects in this type
169 ;; class. UNARY-PREDICATE takes just the object, whereas PREDICATE gets
170 ;; passed both the object and the CTYPE. Normally one or the other will be
171 ;; supplied for any type that can be passed to TYPEP; there is no point in
172 ;; supplying both.
173 (unary-typep nil :type (or symbol null))
174 (typep nil :type (or symbol null))
175 ;; These are like TYPEP and UNARY-TYPEP except they coerce objects to
176 ;; the type.
177 (unary-coerce nil :type (or symbol null))
178 (coerce :type (or symbol null))
181 #!-sb-fluid (declaim (freeze-type type-class))
183 #+sb-xc
184 (eval-when (:compile-toplevel)
185 (assert (= (length (dd-slots (find-defstruct-description 'type-class)))
186 ;; there exist two boolean slots, plus NAME
187 (+ (length !type-class-fun-slots) 3))))
189 (eval-when (#-sb-xc :compile-toplevel :load-toplevel :execute)
190 (defun !type-class-fun-slot (name)
191 (symbolicate "TYPE-CLASS-" name)))
193 ;; Unfortunately redundant with the slots in the DEF!STRUCT,
194 ;; but allows asserting about correctness of the constructor
195 ;; without relying on introspection in host Lisp.
196 (defconstant-eqx !type-class-fun-slots
197 '(simple-subtypep
198 complex-subtypep-arg1
199 complex-subtypep-arg2
200 simple-union2
201 complex-union2
202 simple-intersection2
203 complex-intersection2
204 simple-=
205 complex-=
206 negate
207 unparse
208 singleton-p)
209 #'equal)
211 (defmacro !define-type-method ((class method &rest more-methods)
212 lambda-list &body body)
213 (let ((name (symbolicate class "-" method "-TYPE-METHOD")))
214 `(progn
215 (defun ,name ,lambda-list
216 ,@body)
217 (!cold-init-forms
218 ,@(mapcar (lambda (method)
219 `(setf (,(!type-class-fun-slot method)
220 (type-class-or-lose ',class))
221 #',name))
222 (cons method more-methods)))
223 ',name)))
225 (defmacro !define-type-class (name &key inherits
226 (enumerable (unless inherits (must-supply-this))
227 enumerable-supplied-p)
228 (might-contain-other-types
229 (unless inherits (must-supply-this))
230 might-contain-other-types-supplied-p))
231 (let ((make-it
232 `(let ,(if inherits `((parent (type-class-or-lose ',inherits))))
233 (make-type-class
234 :name ',name
235 :enumerable-p ,(if enumerable-supplied-p
236 enumerable
237 `(type-class-enumerable-p parent))
238 :might-contain-other-types-p
239 ,(if might-contain-other-types-supplied-p
240 might-contain-other-types
241 `(type-class-might-contain-other-types-p parent))
242 ,@(when inherits
243 (loop for name in !type-class-fun-slots
244 append `(,(keywordicate name)
245 (,(!type-class-fun-slot name) parent))))))))
246 #-sb-xc
247 `(progn
248 (eval-when (:compile-toplevel :load-toplevel :execute)
249 (unless (find ',name *type-classes* :key #'type-class-name)
250 (vector-push-extend ,make-it *type-classes*))))
251 #+sb-xc
252 `(!cold-init-forms
253 (setf (svref *type-classes*
254 ,(position name *type-classes* :key #'type-class-name))
255 ,make-it))))
257 ;;; Invoke a type method on TYPE1 and TYPE2. If the two types have the
258 ;;; same class, invoke the simple method. Otherwise, invoke any
259 ;;; complex method. If there isn't a distinct COMPLEX-ARG1 method,
260 ;;; then swap the arguments when calling TYPE1's method. If no
261 ;;; applicable method, return DEFAULT.
263 ;;; KLUDGE: It might be a lot easier to understand this and the rest
264 ;;; of the type system code if we used CLOS to express it instead of
265 ;;; trying to maintain this squirrely hand-crufted object system.
266 ;;; Unfortunately that'd require reworking PCL bootstrapping so that
267 ;;; all the compilation can get done by the cross-compiler, which I
268 ;;; suspect is hard, so we'll bear with the old system for the time
269 ;;; being. -- WHN 2001-03-11
270 (defmacro !invoke-type-method (simple complex-arg2 type1 type2 &key
271 (default '(values nil t))
272 (complex-arg1 :foo complex-arg1-p))
273 (declare (type keyword simple complex-arg1 complex-arg2))
274 (let ((simple (!type-class-fun-slot simple))
275 (cslot1 (!type-class-fun-slot
276 (if complex-arg1-p complex-arg1 complex-arg2)))
277 (cslot2 (!type-class-fun-slot complex-arg2)))
278 (once-only ((ntype1 type1)
279 (ntype2 type2))
280 (once-only ((class1 `(type-class-info ,ntype1))
281 (class2 `(type-class-info ,ntype2)))
282 `(if (eq ,class1 ,class2)
283 (funcall (,simple ,class1) ,ntype1 ,ntype2)
284 ,(once-only ((complex2 `(,cslot2 ,class2)))
285 `(if ,complex2
286 (funcall ,complex2 ,ntype1 ,ntype2)
287 ,(once-only ((complex1 `(,cslot1 ,class1)))
288 `(if ,complex1
289 (if ,complex-arg1-p
290 (funcall ,complex1 ,ntype1 ,ntype2)
291 (funcall ,complex1 ,ntype2 ,ntype1))
292 ,default)))))))))
294 ;;; This is a very specialized implementation of CLOS-style
295 ;;; CALL-NEXT-METHOD within our twisty little type class object
296 ;;; system, which works given that it's called from within a
297 ;;; COMPLEX-SUBTYPEP-ARG2 method. (We're particularly motivated to
298 ;;; implement CALL-NEXT-METHOD in that case, because ANSI imposes some
299 ;;; strict limits on when SUBTYPEP is allowed to return (VALUES NIL NIL),
300 ;;; so instead of just complacently returning (VALUES NIL NIL) from a
301 ;;; COMPLEX-SUBTYPEP-ARG2 method we usually need to CALL-NEXT-METHOD.)
303 ;;; KLUDGE: In CLOS, this could just be CALL-NEXT-METHOD and
304 ;;; everything would Just Work without us having to think about it. In
305 ;;; our goofy type dispatch system, it's messier to express. It's also
306 ;;; more fragile, since (0) there's no check that it's called from
307 ;;; within a COMPLEX-SUBTYPEP-ARG2 method as it should be, and (1) we
308 ;;; rely on our global knowledge that the next (and only) relevant
309 ;;; method is COMPLEX-SUBTYPEP-ARG1, and (2) we rely on our global
310 ;;; knowledge of the appropriate default for the CSUBTYPEP function
311 ;;; when no next method exists. -- WHN 2002-04-07
313 ;;; (We miss CLOS! -- CSR and WHN)
314 (defun invoke-complex-subtypep-arg1-method (type1 type2 &optional subtypep win)
315 (let* ((type-class (type-class-info type1))
316 (method-fun (type-class-complex-subtypep-arg1 type-class)))
317 (if method-fun
318 (funcall (the function method-fun) type1 type2)
319 (values subtypep win))))
321 ;;; KLUDGE: This function is dangerous, as its overuse could easily
322 ;;; cause stack exhaustion through unbounded recursion. We only use
323 ;;; it in one place; maybe it ought not to be a function at all?
324 (defun invoke-complex-=-other-method (type1 type2)
325 (let* ((type-class (type-class-info type1))
326 (method-fun (type-class-complex-= type-class)))
327 (if method-fun
328 (funcall (the function method-fun) type2 type1)
329 (values nil t))))
331 (!defun-from-collected-cold-init-forms !type-class-cold-init)