dcb4f2dd575237d326e3f79e9888e1dc045b24b5
[sbcl.git] / src / code / class.lisp
1 ;;;; This file contains structures and functions for the maintenance of
2 ;;;; basic information about defined types. Different object systems
3 ;;;; can be supported simultaneously. Some of the functions here are
4 ;;;; nominally generic, and are overwritten when CLOS is loaded.
5
6 ;;;; This software is part of the SBCL system. See the README file for
7 ;;;; more information.
8 ;;;;
9 ;;;; This software is derived from the CMU CL system, which was
10 ;;;; written at Carnegie Mellon University and released into the
11 ;;;; public domain. The software is in the public domain and is
12 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
13 ;;;; files for more information.
14
15 (in-package "SB!KERNEL")
16
17 (!begin-collecting-cold-init-forms)
18 \f
19 ;;;; the CLASS structure
20
21 ;;; The CLASS structure is a supertype of all class types. A CLASS is
22 ;;; also a CTYPE structure as recognized by the type system.
23 (def!struct (;; FIXME: Yes, these #+SB-XC/#-SB-XC conditionals are
24              ;; pretty hairy. I'm considering cleaner ways to rewrite
25              ;; the whole build system to avoid these (and other hacks
26              ;; too, e.g. UNCROSS) but I'm not sure yet that I've got
27              ;; it figured out. -- WHN 19990729
28              #-sb-xc sb!xc:class
29              #+sb-xc cl:class
30              (:make-load-form-fun class-make-load-form-fun)
31              (:include ctype
32                        (:class-info (type-class-or-lose #-sb-xc 'sb!xc:class
33                                                         #+sb-xc 'cl:class)))
34              (:constructor nil)
35              #-no-ansi-print-object
36              (:print-object
37               (lambda (class stream)
38                 (let ((name (sb!xc:class-name class)))
39                   (print-unreadable-object (class stream
40                                                   :type t
41                                                   :identity (not name))
42                     (format stream
43                             ;; FIXME: Make sure that this prints
44                             ;; reasonably for anonymous classes.
45                             "~:[anonymous~;~:*~S~]~@[ (~(~A~))~]"
46                             name
47                             (class-state class))))))
48              #-sb-xc-host (:pure nil))
49   ;; the value to be returned by CLASS-NAME. (CMU CL used the raw slot
50   ;; accessor for this slot directly as the definition of
51   ;; CL:CLASS-NAME, but that was slightly wrong, because ANSI says
52   ;; that CL:CLASS-NAME is a generic function.)
53   (%name nil :type symbol)
54   ;; the current layout for this class, or NIL if none assigned yet
55   (layout nil :type (or sb!kernel::layout null))
56   ;; How sure are we that this class won't be redefined?
57   ;;   :READ-ONLY = We are committed to not changing the effective 
58   ;;                slots or superclasses.
59   ;;   :SEALED    = We can't even add subclasses.
60   ;;   NIL        = Anything could happen.
61   (state nil :type (member nil :read-only :sealed))
62   ;; direct superclasses of this class
63   (direct-superclasses () :type list)
64   ;; representation of all of the subclasses (direct or indirect) of
65   ;; this class. This is NIL if no subclasses or not initalized yet;
66   ;; otherwise, it's an EQ hash-table mapping CL:CLASS objects to the
67   ;; subclass layout that was in effect at the time the subclass was
68   ;; created.
69   (subclasses nil :type (or null hash-table))
70   ;; the PCL class object for this class, or NIL if none assigned yet
71   (pcl-class nil))
72
73 ;;; KLUDGE: ANSI says this is a generic function, but we need it for
74 ;;; bootstrapping before CLOS exists, so we define it as an ordinary
75 ;;; function and let CLOS code overwrite it later. -- WHN ca. 19990815
76 (defun sb!xc:class-name (class)
77   (class-%name class))
78
79 (defun class-make-load-form-fun (class)
80   (/show "entering CLASS-MAKE-LOAD-FORM-FUN" class)
81   (let ((name (sb!xc:class-name class)))
82     (unless (and name (eq (sb!xc:find-class name nil) class))
83       (/show "anonymous/undefined class case")
84       (error "can't use anonymous or undefined class as constant:~%  ~S"
85              class))
86     `(locally
87        ;; KLUDGE: There's a FIND-CLASS DEFTRANSFORM for constant class
88        ;; names which creates fast but non-cold-loadable, non-compact
89        ;; code. In this context, we'd rather have compact,
90        ;; cold-loadable code. -- WHN 19990928
91        (declare (notinline sb!xc:find-class))
92        (sb!xc:find-class ',name))))
93 \f
94 ;;;; basic LAYOUT stuff
95
96 ;;; Note: This bound is set somewhat less than MOST-POSITIVE-FIXNUM
97 ;;; in order to guarantee that several hash values can be added without
98 ;;; overflowing into a bignum.
99 (defconstant layout-clos-hash-max (ash most-positive-fixnum -3)
100   #!+sb-doc
101   "the inclusive upper bound on LAYOUT-CLOS-HASH values")
102
103 ;;; a list of conses, initialized by genesis
104 ;;;
105 ;;; In each cons, the car is the symbol naming the layout, and the
106 ;;; cdr is the layout itself.
107 (defvar *!initial-layouts*)
108
109 ;;; a table mapping class names to layouts for classes we have
110 ;;; referenced but not yet loaded. This is initialized from an alist
111 ;;; created by genesis describing the layouts that genesis created at
112 ;;; cold-load time.
113 (defvar *forward-referenced-layouts*)
114 (!cold-init-forms
115   (setq *forward-referenced-layouts* (make-hash-table :test 'equal))
116   #-sb-xc-host (progn
117                  (/show0 "processing *!INITIAL-LAYOUTS*")
118                  (dolist (x *!initial-layouts*)
119                    (setf (gethash (car x) *forward-referenced-layouts*)
120                          (cdr x)))
121                  (/show0 "done processing *!INITIAL-LAYOUTS*")))
122
123 ;;; The LAYOUT structure is pointed to by the first cell of instance
124 ;;; (or structure) objects. It represents what we need to know for
125 ;;; type checking and garbage collection. Whenever a class is
126 ;;; incompatibly redefined, a new layout is allocated. If two object's
127 ;;; layouts are EQ, then they are exactly the same type.
128 ;;;
129 ;;; KLUDGE: The genesis code has raw offsets of slots in this
130 ;;; structure hardwired into it. It would be good to rewrite that code
131 ;;; so that it looks up those offsets in the compiler's tables, but
132 ;;; for now if you change this structure, lucky you, you get to grovel
133 ;;; over the genesis code by hand.:-( -- WHN 19990820
134 (def!struct (layout
135              ;; KLUDGE: A special hack keeps this from being
136              ;; called when building code for the
137              ;; cross-compiler. See comments at the DEFUN for
138              ;; this. -- WHN 19990914
139              (:make-load-form-fun #-sb-xc-host ignore-it
140                                   ;; KLUDGE: DEF!STRUCT at #+SB-XC-HOST
141                                   ;; time controls both the
142                                   ;; build-the-cross-compiler behavior
143                                   ;; and the run-the-cross-compiler
144                                   ;; behavior. The value below only
145                                   ;; works for build-the-cross-compiler.
146                                   ;; There's a special hack in
147                                   ;; EMIT-MAKE-LOAD-FORM which gives
148                                   ;; effectively IGNORE-IT behavior for
149                                   ;; LAYOUT at run-the-cross-compiler
150                                   ;; time. It would be cleaner to
151                                   ;; actually have an IGNORE-IT value
152                                   ;; stored, but it's hard to see how to
153                                   ;; do that concisely with the current
154                                   ;; DEF!STRUCT setup. -- WHN 19990930
155                                   #+sb-xc-host
156                                   make-load-form-for-layout))
157   ;; hash bits which should be set to constant pseudo-random values
158   ;; for use by CLOS. Sleazily accessed via %INSTANCE-REF, see
159   ;; LAYOUT-CLOS-HASH.
160   ;;
161   ;; FIXME: We should get our story straight on what the type of these
162   ;; values is. (declared INDEX here, described as <=
163   ;; LAYOUT-CLOS-HASH-MAX by the doc string of that constant,
164   ;; generated as strictly positive in RANDOM-LAYOUT-CLOS-HASH..)
165   ;;
166   ;; KLUDGE: The fact that the slots here start at offset 1 is known
167   ;; to the LAYOUT-CLOS-HASH function and to the LAYOUT-dumping code
168   ;; in GENESIS.
169   (clos-hash-0 (random-layout-clos-hash) :type index)
170   (clos-hash-1 (random-layout-clos-hash) :type index)
171   (clos-hash-2 (random-layout-clos-hash) :type index)
172   (clos-hash-3 (random-layout-clos-hash) :type index)
173   (clos-hash-4 (random-layout-clos-hash) :type index)
174   (clos-hash-5 (random-layout-clos-hash) :type index)
175   (clos-hash-6 (random-layout-clos-hash) :type index)
176   (clos-hash-7 (random-layout-clos-hash) :type index)
177   ;; the class that this is a layout for
178   (class (required-argument)
179          ;; FIXME: Do we really know this is a CL:CLASS? Mightn't it
180          ;; be a SB-PCL:CLASS under some circumstances? What goes here
181          ;; when the LAYOUT is in fact a PCL::WRAPPER?
182          :type #-sb-xc sb!xc:class #+sb-xc cl:class)
183   ;; The value of this slot can be:
184   ;;   * :UNINITIALIZED if not initialized yet;
185   ;;   * NIL if this is the up-to-date layout for a class; or
186   ;;   * T if this layout has been invalidated (by being replaced by 
187   ;;     a new, more-up-to-date LAYOUT).
188   ;;   * something else (probably a list) if the class is a PCL wrapper
189   ;;     and PCL has made it invalid and made a note to itself about it
190   (invalid :uninitialized :type (or cons (member nil t :uninitialized)))
191   ;; the layouts for all classes we inherit. If hierarchical, i.e. if
192   ;; DEPTHOID >= 0, then these are ordered by ORDER-LAYOUT-INHERITS,
193   ;; so that each inherited layout appears at its expected depth,
194   ;; i.e. at its LAYOUT-DEPTHOID value.
195   ;;
196   ;; Remaining elements are filled by the non-hierarchical layouts or,
197   ;; if they would otherwise be empty, by copies of succeeding layouts.
198   (inherits #() :type simple-vector)
199   ;; If inheritance is not hierarchical, this is -1. If inheritance is 
200   ;; hierarchical, this is the inheritance depth, i.e. (LENGTH INHERITS).
201   ;; Note:
202   ;;  (1) This turns out to be a handy encoding for arithmetically
203   ;;      comparing deepness; it is generally useful to do a bare numeric
204   ;;      comparison of these depthoid values, and we hardly ever need to
205   ;;      test whether the values are negative or not.
206   ;;  (2) This was called INHERITANCE-DEPTH in classic CMU CL. It was
207   ;;      renamed because some of us find it confusing to call something
208   ;;      a depth when it isn't quite.
209   (depthoid -1 :type layout-depthoid)
210   ;; The number of top-level descriptor cells in each instance.
211   (length 0 :type index)
212   ;; If this layout has some kind of compiler meta-info, then this is
213   ;; it. If a structure, then we store the DEFSTRUCT-DESCRIPTION here.
214   (info nil)
215   ;; This is true if objects of this class are never modified to
216   ;; contain dynamic pointers in their slots or constant-like
217   ;; substructure (and hence can be copied into read-only space by
218   ;; PURIFY).
219   ;;
220   ;; KLUDGE: This slot is known to the C runtime support code.
221   (pure nil :type (member t nil 0)))
222
223 (def!method print-object ((layout layout) stream)
224   (print-unreadable-object (layout stream :type t :identity t)
225     (format stream
226             "for ~S~@[, INVALID=~S~]"
227             (layout-proper-name layout)
228             (layout-invalid layout))))
229
230 (eval-when (:compile-toplevel :load-toplevel :execute)
231   (defun layout-proper-name (layout)
232     (class-proper-name (layout-class layout))))
233 \f
234 ;;;; support for the hash values used by CLOS when working with LAYOUTs
235
236 (defconstant layout-clos-hash-length 8)
237 #!-sb-fluid (declaim (inline layout-clos-hash))
238 (defun layout-clos-hash (layout i)
239   ;; FIXME: Either this I should be declared to be `(MOD
240   ;; ,LAYOUT-CLOS-HASH-LENGTH), or this is used in some inner loop
241   ;; where we can't afford to check that kind of thing and therefore
242   ;; should have some insane level of optimization. (This is true both
243   ;; of this function and of the SETF function below.)
244   (declare (type layout layout) (type index i))
245   ;; FIXME: LAYOUT slots should have type `(MOD ,LAYOUT-CLOS-HASH-MAX),
246   ;; not INDEX.
247   (truly-the index (%instance-ref layout (1+ i))))
248 #!-sb-fluid (declaim (inline (setf layout-clos-hash)))
249 (defun (setf layout-clos-hash) (new-value layout i)
250   (declare (type layout layout) (type index new-value i))
251   (setf (%instance-ref layout (1+ i)) new-value))
252
253 ;;; a generator for random values suitable for the CLOS-HASH slots of
254 ;;; LAYOUTs. We use our own RANDOM-STATE here because we'd like
255 ;;; pseudo-random values to come the same way in the target even when
256 ;;; we make minor changes to the system, in order to reduce the
257 ;;; mysteriousness of possible CLOS bugs.
258 (defvar *layout-clos-hash-random-state*)
259 (defun random-layout-clos-hash ()
260   ;; FIXME: I'm not sure why this expression is (1+ (RANDOM FOO)),
261   ;; returning a strictly positive value. I copied it verbatim from
262   ;; CMU CL INITIALIZE-LAYOUT-HASH, so presumably it works, but I
263   ;; dunno whether the hash values are really supposed to be 1-based.
264   ;; They're declared as INDEX.. Or is this a hack to try to avoid
265   ;; having to use bignum arithmetic? Or what? An explanation would be
266   ;; nice.
267   (1+ (random layout-clos-hash-max
268               (if (boundp '*layout-clos-hash-random-state*)
269                   *layout-clos-hash-random-state*
270                   (setf *layout-clos-hash-random-state*
271                         (make-random-state))))))
272 \f
273 ;;; If we can't find any existing layout, then we create a new one
274 ;;; storing it in *FORWARD-REFERENCED-LAYOUTS*. In classic CMU CL, we
275 ;;; used to immediately check for compatibility, but for
276 ;;; cross-compilability reasons (i.e. convenience of using this
277 ;;; function in a MAKE-LOAD-FORM expression) that functionality has
278 ;;; been split off into INIT-OR-CHECK-LAYOUT.
279 (declaim (ftype (function (symbol) layout) find-layout))
280 (defun find-layout (name)
281   (let ((class (sb!xc:find-class name nil)))
282     (or (and class (class-layout class))
283         (gethash name *forward-referenced-layouts*)
284         (setf (gethash name *forward-referenced-layouts*)
285               (make-layout :class (or class (make-undefined-class name)))))))
286
287 ;;; If LAYOUT is uninitialized, initialize it with CLASS, LENGTH,
288 ;;; INHERITS, and DEPTHOID, otherwise require that it be consistent
289 ;;; with CLASS, LENGTH, INHERITS, and DEPTHOID.
290 ;;;
291 ;;; UNDEFINED-CLASS values are interpreted specially as "we don't know
292 ;;; anything about the class", so if LAYOUT is initialized, any
293 ;;; preexisting class slot value is OK, and if it's not initialized,
294 ;;; its class slot value is set to an UNDEFINED-CLASS. -- FIXME: This
295 ;;; is no longer true, :UNINITIALIZED used instead.
296 (declaim (ftype (function (layout sb!xc:class index simple-vector layout-depthoid) layout)
297                 init-or-check-layout))
298 (defun init-or-check-layout (layout class length inherits depthoid)
299   (cond ((eq (layout-invalid layout) :uninitialized)
300          ;; There was no layout before, we just created one which
301          ;; we'll now initialize with our information.
302          (setf (layout-length layout) length
303                (layout-inherits layout) inherits
304                (layout-depthoid layout) depthoid
305                (layout-class layout) class
306                (layout-invalid layout) nil))
307         ;; FIXME: Now that LAYOUTs are born :UNINITIALIZED, maybe this
308         ;; clause is not needed?
309         ((not *type-system-initialized*)
310          (setf (layout-class layout) class))
311         (t
312          ;; There was an old layout already initialized with old
313          ;; information, and we'll now check that old information
314          ;; which was known with certainty is consistent with current
315          ;; information which is known with certainty.
316          (check-layout layout class length inherits depthoid)))
317   layout)
318
319 ;;; In code for the target Lisp, we don't use dump LAYOUTs using the
320 ;;; standard load form mechanism, we use special fops instead, in
321 ;;; order to make cold load come out right. But when we're building
322 ;;; the cross-compiler, we can't do that because we don't have access
323 ;;; to special non-ANSI low-level things like special fops, and we
324 ;;; don't need to do that anyway because our code isn't going to be
325 ;;; cold loaded, so we use the ordinary load form system.
326 ;;;
327 ;;; KLUDGE: A special hack causes this not to be called when we are
328 ;;; building code for the target Lisp. It would be tidier to just not
329 ;;; have it in place when we're building the target Lisp, but it
330 ;;; wasn't clear how to do that without rethinking DEF!STRUCT quite a
331 ;;; bit, so I punted. -- WHN 19990914
332 #+sb-xc-host
333 (defun make-load-form-for-layout (layout &optional env)
334   (declare (type layout layout))
335   (declare (ignore env))
336   (when (layout-invalid layout)
337     (compiler-error "can't dump reference to obsolete class: ~S"
338                     (layout-class layout)))
339   (let ((name (sb!xc:class-name (layout-class layout))))
340     (unless name
341       (compiler-error "can't dump anonymous LAYOUT: ~S" layout))
342     ;; Since LAYOUT refers to a class which refers back to the LAYOUT,
343     ;; we have to do this in two stages, like the TREE-WITH-PARENT
344     ;; example in the MAKE-LOAD-FORM entry in the ANSI spec.
345     (values
346      ;; "creation" form (which actually doesn't create a new LAYOUT if
347      ;; there's a preexisting one with this name)
348      `(find-layout ',name)
349      ;; "initialization" form (which actually doesn't initialize
350      ;; preexisting LAYOUTs, just checks that they're consistent).
351      `(init-or-check-layout ',layout
352                             ',(layout-class layout)
353                             ',(layout-length layout)
354                             ',(layout-inherits layout)
355                             ',(layout-depthoid layout)))))
356
357 ;;; If LAYOUT's slot values differ from the specified slot values in
358 ;;; any interesting way, then give a warning and return T.
359 (declaim (ftype (function (simple-string
360                            layout
361                            simple-string
362                            index
363                            simple-vector
364                            layout-depthoid))
365                 redefine-layout-warning))
366 (defun redefine-layout-warning (old-context old-layout
367                                 context length inherits depthoid)
368   (declare (type layout old-layout) (type simple-string old-context context))
369   (let ((name (layout-proper-name old-layout)))
370     (or (let ((old-inherits (layout-inherits old-layout)))
371           (or (when (mismatch old-inherits
372                               inherits
373                               :key #'layout-proper-name)
374                 (warn "change in superclasses of class ~S:~%  ~
375                        ~A superclasses: ~S~%  ~
376                        ~A superclasses: ~S"
377                       name
378                       old-context
379                       (map 'list #'layout-proper-name old-inherits)
380                       context
381                       (map 'list #'layout-proper-name inherits))
382                 t)
383               (let ((diff (mismatch old-inherits inherits)))
384                 (when diff
385                   (warn
386                    "in class ~S:~%  ~
387                     ~:(~A~) definition of superclass ~S is incompatible with~%  ~
388                     ~A definition."
389                    name
390                    old-context
391                    (layout-proper-name (svref old-inherits diff))
392                    context)
393                   t))))
394         (let ((old-length (layout-length old-layout)))
395           (unless (= old-length length)
396             (warn "change in instance length of class ~S:~%  ~
397                    ~A length: ~D~%  ~
398                    ~A length: ~D"
399                   name
400                   old-context old-length
401                   context length)
402             t))
403         (unless (= (layout-depthoid old-layout) depthoid)
404           (warn "change in the inheritance structure of class ~S~%  ~
405                  between the ~A definition and the ~A definition"
406                 name old-context context)
407           t))))
408
409 ;;; Require that LAYOUT data be consistent with CLASS, LENGTH,
410 ;;; INHERITS, and DEPTHOID.
411 (declaim (ftype (function (layout sb!xc:class index simple-vector layout-depthoid))
412                 check-layout))
413 (defun check-layout (layout class length inherits depthoid)
414   (aver (eq (layout-class layout) class))
415   (when (redefine-layout-warning "current" layout
416                                  "compile time" length inherits depthoid)
417     ;; Classic CMU CL had more options here. There are several reasons
418     ;; why they might want more options which are less appropriate for
419     ;; us: (1) It's hard to fit the classic CMU CL flexible approach
420     ;; into the ANSI-style MAKE-LOAD-FORM system, and having a
421     ;; non-MAKE-LOAD-FORM-style system is painful when we're trying to
422     ;; make the cross-compiler run under vanilla ANSI Common Lisp. (2)
423     ;; We have CLOS now, and if you want to be able to flexibly
424     ;; redefine classes without restarting the system, it'd make sense
425     ;; to use that, so supporting complexity in order to allow
426     ;; modifying DEFSTRUCTs without restarting the system is a low
427     ;; priority. (3) We now have the ability to rebuild the SBCL
428     ;; system from scratch, so we no longer need this functionality in
429     ;; order to maintain the SBCL system by modifying running images.
430     (error "The class ~S was not changed, and there's no guarantee that~@
431             the loaded code (which expected another layout) will work."
432            (layout-proper-name layout)))
433   (values))
434
435 ;;; a common idiom (the same as CMU CL FIND-LAYOUT) rolled up into a
436 ;;; single function call
437 ;;;
438 ;;; Used by the loader to forward-reference layouts for classes whose
439 ;;; definitions may not have been loaded yet. This allows type tests
440 ;;; to be loaded when the type definition hasn't been loaded yet.
441 (declaim (ftype (function (symbol index simple-vector layout-depthoid) layout)
442                 find-and-init-or-check-layout))
443 (defun find-and-init-or-check-layout (name length inherits depthoid)
444   (/show0 "entering FIND-AND-INIT-OR-CHECK-LAYOUT")
445   (let ((layout (find-layout name)))
446     (init-or-check-layout layout
447                           (or (sb!xc:find-class name nil)
448                               (make-undefined-class name))
449                           length
450                           inherits
451                           depthoid)))
452
453 ;;; Record LAYOUT as the layout for its class, adding it as a subtype
454 ;;; of all superclasses. This is the operation that "installs" a
455 ;;; layout for a class in the type system, clobbering any old layout.
456 ;;; However, this does not modify the class namespace; that is a
457 ;;; separate operation (think anonymous classes.)
458 ;;; -- If INVALIDATE, then all the layouts for any old definition
459 ;;;    and subclasses are invalidated, and the SUBCLASSES slot is cleared.
460 ;;; -- If DESTRUCT-LAYOUT, then this is some old layout, and is to be
461 ;;;    destructively modified to hold the same type information.
462 (eval-when (#-sb-xc :compile-toplevel :load-toplevel :execute)
463 (defun register-layout (layout &key (invalidate t) destruct-layout)
464   (declare (type layout layout) (type (or layout null) destruct-layout))
465   (let* ((class (layout-class layout))
466          (class-layout (class-layout class))
467          (subclasses (class-subclasses class)))
468
469     ;; Attempting to register ourselves with a temporary undefined
470     ;; class placeholder is almost certainly a programmer error. (I
471     ;; should know, I did it.) -- WHN 19990927
472     (aver (not (undefined-class-p class)))
473
474     ;; This assertion dates from classic CMU CL. The rationale is
475     ;; probably that calling REGISTER-LAYOUT more than once for the
476     ;; same LAYOUT is almost certainly a programmer error.
477     (aver (not (eq class-layout layout)))
478
479     ;; Figure out what classes are affected by the change, and issue
480     ;; appropriate warnings and invalidations.
481     (when class-layout
482       (modify-class class)
483       (when subclasses
484         (dohash (subclass subclass-layout subclasses)
485           (modify-class subclass)
486           (when invalidate
487             (invalidate-layout subclass-layout))))
488       (when invalidate
489         (invalidate-layout class-layout)
490         (setf (class-subclasses class) nil)))
491
492     (if destruct-layout
493         (setf (layout-invalid destruct-layout) nil
494               (layout-inherits destruct-layout) (layout-inherits layout)
495               (layout-depthoid destruct-layout)(layout-depthoid layout)
496               (layout-length destruct-layout) (layout-length layout)
497               (layout-info destruct-layout) (layout-info layout)
498               (class-layout class) destruct-layout)
499         (setf (layout-invalid layout) nil
500               (class-layout class) layout))
501
502     (let ((inherits (layout-inherits layout)))
503       (dotimes (i (length inherits)) ; FIXME: should be DOVECTOR
504         (let* ((super (layout-class (svref inherits i)))
505                (subclasses (or (class-subclasses super)
506                                (setf (class-subclasses super)
507                                      (make-hash-table :test 'eq)))))
508           (when (and (eq (class-state super) :sealed)
509                      (not (gethash class subclasses)))
510             (warn "unsealing sealed class ~S in order to subclass it"
511                   (sb!xc:class-name super))
512             (setf (class-state super) :read-only))
513           (setf (gethash class subclasses)
514                 (or destruct-layout layout))))))
515
516   (values))
517 ); EVAL-WHEN
518
519 ;;; Arrange the inherited layouts to appear at their expected depth,
520 ;;; ensuring that hierarchical type tests succeed. Layouts with 
521 ;;; DEPTHOID >= 0 (i.e. hierarchical classes) are placed first,
522 ;;; at exactly that index in the INHERITS vector. Then, non-hierarchical
523 ;;; layouts are placed in remaining elements. Then, any still-empty
524 ;;; elements are filled with their successors, ensuring that each
525 ;;; element contains a valid layout.
526 ;;;
527 ;;; This reordering may destroy CPL ordering, so the inherits should
528 ;;; not be read as being in CPL order.
529 (defun order-layout-inherits (layouts)
530   (declare (simple-vector layouts))
531   (let ((length (length layouts))
532         (max-depth -1))
533     (dotimes (i length)
534       (let ((depth (layout-depthoid (svref layouts i))))
535         (when (> depth max-depth)
536           (setf max-depth depth))))
537     (let* ((new-length (max (1+ max-depth) length))
538            (inherits (make-array new-length)))
539       (dotimes (i length)
540         (let* ((layout (svref layouts i))
541                (depth (layout-depthoid layout)))
542           (unless (eql depth -1)
543             (let ((old-layout (svref inherits depth)))
544               (unless (or (eql old-layout 0) (eq old-layout layout))
545                 (error "layout depth conflict: ~S~%" layouts)))
546             (setf (svref inherits depth) layout))))
547       (do ((i 0 (1+ i))
548            (j 0))
549           ((>= i length))
550         (declare (type index i j))
551         (let* ((layout (svref layouts i))
552                (depth (layout-depthoid layout)))
553           (when (eql depth -1)
554             (loop (when (eql (svref inherits j) 0)
555                     (return))
556                   (incf j))
557             (setf (svref inherits j) layout))))
558       (do ((i (1- new-length) (1- i)))
559           ((< i 0))
560         (declare (type fixnum i))
561         (when (eql (svref inherits i) 0)
562           (setf (svref inherits i) (svref inherits (1+ i)))))
563       inherits)))
564 \f
565 ;;;; class precedence lists
566
567 ;;; Topologically sort the list of objects to meet a set of ordering
568 ;;; constraints given by pairs (A . B) constraining A to precede B.
569 ;;; When there are multiple objects to choose, the tie-breaker
570 ;;; function is called with both the list of object to choose from and
571 ;;; the reverse ordering built so far.
572 (defun topological-sort (objects constraints tie-breaker)
573   (declare (list objects constraints)
574            (function tie-breaker))
575   (let ((obj-info (make-hash-table :size (length objects)))
576         (free-objs nil)
577         (result nil))
578     (dolist (constraint constraints)
579       (let ((obj1 (car constraint))
580             (obj2 (cdr constraint)))
581         (let ((info2 (gethash obj2 obj-info)))
582           (if info2
583               (incf (first info2))
584               (setf (gethash obj2 obj-info) (list 1))))
585         (let ((info1 (gethash obj1 obj-info)))
586           (if info1
587               (push obj2 (rest info1))
588               (setf (gethash obj1 obj-info) (list 0 obj2))))))
589     (dolist (obj objects)
590       (let ((info (gethash obj obj-info)))
591         (when (or (not info) (zerop (first info)))
592           (push obj free-objs))))
593     (loop
594      (flet ((next-result (obj)
595               (push obj result)
596               (dolist (successor (rest (gethash obj obj-info)))
597                 (let* ((successor-info (gethash successor obj-info))
598                        (count (1- (first successor-info))))
599                   (setf (first successor-info) count)
600                   (when (zerop count)
601                     (push successor free-objs))))))
602        (cond ((endp free-objs)
603               (dohash (obj info obj-info)
604                 (unless (zerop (first info))
605                   (error "Topological sort failed due to constraint on ~S."
606                          obj)))
607               (return (nreverse result)))
608              ((endp (rest free-objs))
609               (next-result (pop free-objs)))
610              (t
611               (let ((obj (funcall tie-breaker free-objs result)))
612                 (setf free-objs (remove obj free-objs))
613                 (next-result obj))))))))
614
615
616 ;;; standard class precedence list computation
617 (defun std-compute-class-precedence-list (class)
618   (let ((classes nil)
619         (constraints nil))
620     (labels ((note-class (class)
621                (unless (member class classes)
622                  (push class classes)
623                  (let ((superclasses (class-direct-superclasses class)))
624                    (do ((prev class)
625                         (rest superclasses (rest rest)))
626                        ((endp rest))
627                      (let ((next (first rest)))
628                        (push (cons prev next) constraints)
629                        (setf prev next)))
630                    (dolist (class superclasses)
631                      (note-class class)))))
632              (std-cpl-tie-breaker (free-classes rev-cpl)
633                (dolist (class rev-cpl (first free-classes))
634                  (let* ((superclasses (class-direct-superclasses class))
635                         (intersection (intersection free-classes
636                                                     superclasses)))
637                    (when intersection
638                      (return (first intersection)))))))
639       (note-class class)
640       (topological-sort classes constraints #'std-cpl-tie-breaker))))
641 \f
642 ;;;; object types to represent classes
643
644 ;;; An UNDEFINED-CLASS is a cookie we make up to stick in forward
645 ;;; referenced layouts. Users should never see them.
646 (def!struct (undefined-class (:include #-sb-xc sb!xc:class
647                                        #+sb-xc cl:class)
648                              (:constructor make-undefined-class (%name))))
649
650 ;;; BUILT-IN-CLASS is used to represent the standard classes that
651 ;;; aren't defined with DEFSTRUCT and other specially implemented
652 ;;; primitive types whose only attribute is their name.
653 ;;;
654 ;;; Some BUILT-IN-CLASSes have a TRANSLATION, which means that they
655 ;;; are effectively DEFTYPE'd to some other type (usually a union of
656 ;;; other classes or a "primitive" type such as NUMBER, ARRAY, etc.)
657 ;;; This translation is done when type specifiers are parsed. Type
658 ;;; system operations (union, subtypep, etc.) should never encounter
659 ;;; translated classes, only their translation.
660 (def!struct (sb!xc:built-in-class (:include #-sb-xc sb!xc:class
661                                             #+sb-xc cl:class)
662                                   (:constructor bare-make-built-in-class))
663   ;; the type we translate to on parsing. If NIL, then this class
664   ;; stands on its own; or it can be set to :INITIALIZING for a period
665   ;; during cold-load.
666   (translation nil :type (or ctype (member nil :initializing))))
667 (defun make-built-in-class (&rest rest)
668   (apply #'bare-make-built-in-class
669          (rename-key-args '((:name :%name)) rest)))
670
671 ;;; FIXME: In CMU CL, this was a class with a print function, but not
672 ;;; necessarily a structure class (e.g. CONDITIONs). In SBCL,
673 ;;; we let CLOS handle our print functions, so that is no longer needed.
674 ;;; Is there any need for this class any more?
675 (def!struct (slot-class (:include #-sb-xc sb!xc:class #+sb-xc cl:class)
676                         (:constructor nil)))
677
678 ;;; STRUCTURE-CLASS represents what we need to know about structure
679 ;;; classes. Non-structure "typed" defstructs are a special case, and
680 ;;; don't have a corresponding class.
681 (def!struct (basic-structure-class (:include slot-class)
682                                    (:constructor nil)))
683
684 (def!struct (sb!xc:structure-class (:include basic-structure-class)
685                                    (:constructor bare-make-structure-class))
686   ;; If true, a default keyword constructor for this structure.
687   (constructor nil :type (or function null)))
688 (defun make-structure-class (&rest rest)
689   (apply #'bare-make-structure-class
690          (rename-key-args '((:name :%name)) rest)))
691
692 ;;; FUNCALLABLE-STRUCTURE-CLASS is used to represent funcallable
693 ;;; structures, which are used to implement generic functions.
694 (def!struct (funcallable-structure-class (:include basic-structure-class)
695                                          (:constructor bare-make-funcallable-structure-class)))
696 (defun make-funcallable-structure-class (&rest rest)
697   (apply #'bare-make-funcallable-structure-class
698          (rename-key-args '((:name :%name)) rest)))
699 \f
700 ;;;; class namespace
701
702 ;;; We use an indirection to allow forward referencing of class
703 ;;; definitions with load-time resolution.
704 (def!struct (class-cell
705              (:constructor make-class-cell (name &optional class))
706              (:make-load-form-fun (lambda (c)
707                                     `(find-class-cell ',(class-cell-name c))))
708              #-no-ansi-print-object
709              (:print-object (lambda (s stream)
710                               (print-unreadable-object (s stream :type t)
711                                 (prin1 (class-cell-name s) stream)))))
712   ;; Name of class we expect to find.
713   (name nil :type symbol :read-only t)
714   ;; Class or NIL if not yet defined.
715   (class nil :type (or #-sb-xc sb!xc:class #+sb-xc cl:class
716                        null)))
717 (defun find-class-cell (name)
718   (or (info :type :class name)
719       (setf (info :type :class name)
720             (make-class-cell name))))
721
722 ;;; FIXME: When the system is stable, this DECLAIM FTYPE should
723 ;;; probably go away in favor of the DEFKNOWN for FIND-CLASS.
724 (declaim (ftype (function (symbol &optional t (or null sb!c::lexenv))) sb!xc:find-class))
725 (eval-when (#-sb-xc :compile-toplevel :load-toplevel :execute)
726 (defun sb!xc:find-class (name &optional (errorp t) environment)
727   #!+sb-doc
728   "Return the class with the specified NAME. If ERRORP is false, then NIL is
729    returned when no such class exists."
730   (declare (type symbol name) (ignore environment))
731   (let ((res (class-cell-class (find-class-cell name))))
732     (if (or res (not errorp))
733         res
734         (error "class not yet defined:~%  ~S" name))))
735 (defun (setf sb!xc:find-class) (new-value name)
736   #-sb-xc (declare (type sb!xc:class new-value))
737   (ecase (info :type :kind name)
738     ((nil))
739     (:instance
740      (let ((old (class-of (sb!xc:find-class name)))
741            (new (class-of new-value)))
742        (unless (eq old new)
743          (warn "changing meta-class of ~S from ~S to ~S"
744                name
745                (class-name old)
746                (class-name new)))))
747     (:primitive
748      (error "illegal to redefine standard type ~S" name))
749     (:defined
750      (warn "redefining DEFTYPE type to be a class: ~S" name)
751      (setf (info :type :expander name) nil)))
752
753   (remhash name *forward-referenced-layouts*)
754   (%note-type-defined name)
755   (setf (info :type :kind name) :instance)
756   (setf (class-cell-class (find-class-cell name)) new-value)
757   (unless (eq (info :type :compiler-layout name)
758               (class-layout new-value))
759     (setf (info :type :compiler-layout name) (class-layout new-value)))
760   new-value)
761 ) ; EVAL-WHEN
762
763 ;;; Called when we are about to define NAME as a class meeting some
764 ;;; predicate (such as a meta-class type test.) The first result is
765 ;;; always of the desired class. The second result is any existing
766 ;;; LAYOUT for this name.
767 (defun insured-find-class (name predicate constructor)
768   (declare (type function predicate constructor))
769   (let* ((old (sb!xc:find-class name nil))
770          (res (if (and old (funcall predicate old))
771                   old
772                   (funcall constructor :name name)))
773          (found (or (gethash name *forward-referenced-layouts*)
774                     (when old (class-layout old)))))
775     (when found
776       (setf (layout-class found) res))
777     (values res found)))
778
779 ;;; If the class has a proper name, return the name, otherwise return
780 ;;; the class.
781 (defun class-proper-name (class)
782   #-sb-xc (declare (type sb!xc:class class))
783   (let ((name (sb!xc:class-name class)))
784     (if (and name (eq (sb!xc:find-class name nil) class))
785         name
786         class)))
787 \f
788 ;;;; CLASS type operations
789
790 (!define-type-class sb!xc:class)
791
792 ;;; Simple methods for TYPE= and SUBTYPEP should never be called when
793 ;;; the two classes are equal, since there are EQ checks in those
794 ;;; operations.
795 (!define-type-method (sb!xc:class :simple-=) (type1 type2)
796   (aver (not (eq type1 type2)))
797   (values nil t))
798
799 (!define-type-method (sb!xc:class :simple-subtypep) (class1 class2)
800   (aver (not (eq class1 class2)))
801   (let ((subclasses (class-subclasses class2)))
802     (if (and subclasses (gethash class1 subclasses))
803         (values t t)
804         (values nil t))))
805
806 ;;; When finding the intersection of a sealed class and some other
807 ;;; class (not hierarchically related) the intersection is the union
808 ;;; of the currently shared subclasses.
809 (defun sealed-class-intersection2 (sealed other)
810   (declare (type sb!xc:class sealed other))
811   (let ((s-sub (class-subclasses sealed))
812         (o-sub (class-subclasses other)))
813     (if (and s-sub o-sub)
814         (collect ((res *empty-type* type-union))
815           (dohash (subclass layout s-sub)
816             (declare (ignore layout))
817             (when (gethash subclass o-sub)
818               (res (specifier-type subclass))))
819           (res))
820         *empty-type*)))
821
822 (!define-type-method (sb!xc:class :simple-intersection2) (class1 class2)
823   (declare (type sb!xc:class class1 class2))
824   (cond ((eq class1 class2)
825          class1)
826         ;; If one is a subclass of the other, then that is the
827         ;; intersection.
828         ((let ((subclasses (class-subclasses class2)))
829            (and subclasses (gethash class1 subclasses)))
830          class1)
831         ((let ((subclasses (class-subclasses class1)))
832            (and subclasses (gethash class2 subclasses)))
833          class2)
834         ;; Otherwise, we can't in general be sure that the
835         ;; intersection is empty, since a subclass of both might be
836         ;; defined. But we can eliminate it for some special cases.
837         ((or (basic-structure-class-p class1)
838              (basic-structure-class-p class2))
839          ;; No subclass of both can be defined.
840          *empty-type*)
841         ((eq (class-state class1) :sealed)
842          ;; checking whether a subclass of both can be defined:
843          (sealed-class-intersection2 class1 class2))
844         ((eq (class-state class2) :sealed)
845          ;; checking whether a subclass of both can be defined:
846          (sealed-class-intersection2 class2 class1))
847         (t
848          ;; uncertain, since a subclass of both might be defined
849          nil)))
850
851 (!define-type-method (sb!xc:class :unparse) (type)
852   (class-proper-name type))
853 \f
854 ;;;; PCL stuff
855
856 (def!struct (std-class (:include sb!xc:class)
857                        (:constructor nil)))
858 (def!struct (sb!xc:standard-class (:include std-class)
859                                   (:constructor bare-make-standard-class)))
860 (def!struct (random-pcl-class (:include std-class)
861                               (:constructor bare-make-random-pcl-class)))
862 (defun make-standard-class (&rest rest)
863   (apply #'bare-make-standard-class
864          (rename-key-args '((:name :%name)) rest)))
865 (defun make-random-pcl-class (&rest rest)
866   (apply #'bare-make-random-pcl-class
867          (rename-key-args '((:name :%name)) rest)))
868 \f
869 ;;;; built-in classes
870
871 ;;; The BUILT-IN-CLASSES list is a data structure which configures the
872 ;;; creation of all the built-in classes. It contains all the info
873 ;;; that we need to maintain the mapping between classes, compile-time
874 ;;; types and run-time type codes. These options are defined:
875 ;;;
876 ;;; :TRANSLATION (default none)
877 ;;;     When this class is "parsed" as a type specifier, it is
878 ;;;     translated into the specified internal type representation,
879 ;;;     rather than being left as a class. This is used for types
880 ;;;     which we want to canonicalize to some other kind of type
881 ;;;     object because in general we want to be able to include more
882 ;;;     information than just the class (e.g. for numeric types.)
883 ;;;
884 ;;; :ENUMERABLE (default NIL)
885 ;;;     The value of the :ENUMERABLE slot in the created class.
886 ;;;     Meaningless in translated classes.
887 ;;;
888 ;;; :STATE (default :SEALED)
889 ;;;     The value of CLASS-STATE which we want on completion,
890 ;;;     indicating whether subclasses can be created at run-time.
891 ;;;
892 ;;; :HIERARCHICAL-P (default T unless any of the inherits are non-hierarchical)
893 ;;;     True if we can assign this class a unique inheritance depth.
894 ;;;
895 ;;; :CODES (default none)
896 ;;;     Run-time type codes which should be translated back to this
897 ;;;     class by CLASS-OF. Unspecified for abstract classes.
898 ;;;
899 ;;; :INHERITS (default this class and T)
900 ;;;     The class-precedence list for this class, with this class and
901 ;;;     T implicit.
902 ;;;
903 ;;; :DIRECT-SUPERCLASSES (default to head of CPL)
904 ;;;     List of the direct superclasses of this class.
905 ;;;
906 ;;; FIXME: This doesn't seem to be needed after cold init (and so can
907 ;;; probably be uninterned at the end of cold init).
908 (defvar *built-in-classes*)
909 (!cold-init-forms
910   (/show0 "setting *BUILT-IN-CLASSES*")
911   (setq
912    *built-in-classes*
913    '((t :state :read-only :translation t)
914      (character :enumerable t :translation base-char)
915      (base-char :enumerable t
916                 :inherits (character)
917                 :codes (#.sb!vm:base-char-type))
918      (symbol :codes (#.sb!vm:symbol-header-type))
919
920      (instance :state :read-only)
921
922      (system-area-pointer :codes (#.sb!vm:sap-type))
923      (weak-pointer :codes (#.sb!vm:weak-pointer-type))
924      (code-component :codes (#.sb!vm:code-header-type))
925      #!-gengc (lra :codes (#.sb!vm:return-pc-header-type))
926      (fdefn :codes (#.sb!vm:fdefn-type))
927      (random-class) ; used for unknown type codes
928
929      (function
930       :codes (#.sb!vm:byte-code-closure-type
931               #.sb!vm:byte-code-function-type
932               #.sb!vm:closure-header-type
933               #.sb!vm:function-header-type)
934       :state :read-only)
935      (funcallable-instance
936       :inherits (function)
937       :state :read-only)
938
939      ;; FIXME: Are COLLECTION and MUTABLE-COLLECTION used for anything
940      ;; any more? COLLECTION is not defined in ANSI Common Lisp..
941      (collection :hierarchical-p nil :state :read-only)
942      (mutable-collection :state :read-only
943                          :inherits (collection))
944      (generic-sequence :state :read-only
945                        :inherits (collection))
946      (mutable-sequence :state :read-only
947                        :direct-superclasses (mutable-collection
948                                              generic-sequence)
949                        :inherits (mutable-collection
950                                   generic-sequence
951                                   collection))
952      (generic-array :state :read-only
953                     :inherits (mutable-sequence
954                                mutable-collection
955                                generic-sequence
956                                collection))
957      (generic-vector :state :read-only
958                      :inherits (generic-array
959                                 mutable-sequence mutable-collection
960                                 generic-sequence collection))
961      (array :translation array :codes (#.sb!vm:complex-array-type)
962             :inherits (generic-array mutable-sequence mutable-collection
963                                      generic-sequence collection))
964      (simple-array
965       :translation simple-array :codes (#.sb!vm:simple-array-type)
966       :inherits (array generic-array mutable-sequence mutable-collection
967                  generic-sequence collection))
968      (sequence
969       :translation (or cons (member nil) vector)
970       :inherits (mutable-sequence mutable-collection generic-sequence
971                  collection))
972      (vector
973       :translation vector :codes (#.sb!vm:complex-vector-type)
974       :direct-superclasses (array sequence generic-vector)
975       :inherits (array sequence generic-vector generic-array
976                  mutable-sequence mutable-collection generic-sequence
977                  collection))
978      (simple-vector
979       :translation simple-vector :codes (#.sb!vm:simple-vector-type)
980       :direct-superclasses (vector simple-array)
981       :inherits (vector simple-array array
982                  sequence generic-vector generic-array
983                  mutable-sequence mutable-collection
984                  generic-sequence collection))
985      (bit-vector
986       :translation bit-vector :codes (#.sb!vm:complex-bit-vector-type)
987       :inherits (vector array sequence
988                  generic-vector generic-array mutable-sequence
989                  mutable-collection generic-sequence collection))
990      (simple-bit-vector
991       :translation simple-bit-vector :codes (#.sb!vm:simple-bit-vector-type)
992       :direct-superclasses (bit-vector simple-array)
993       :inherits (bit-vector vector simple-array
994                  array sequence
995                  generic-vector generic-array mutable-sequence
996                  mutable-collection generic-sequence collection))
997      (simple-array-unsigned-byte-2
998       :translation (simple-array (unsigned-byte 2) (*))
999       :codes (#.sb!vm:simple-array-unsigned-byte-2-type)
1000       :direct-superclasses (vector simple-array)
1001       :inherits (vector simple-array array sequence
1002                  generic-vector generic-array mutable-sequence
1003                  mutable-collection generic-sequence collection))
1004      (simple-array-unsigned-byte-4
1005       :translation (simple-array (unsigned-byte 4) (*))
1006       :codes (#.sb!vm:simple-array-unsigned-byte-4-type)
1007       :direct-superclasses (vector simple-array)
1008       :inherits (vector simple-array array sequence
1009                  generic-vector generic-array mutable-sequence
1010                  mutable-collection generic-sequence collection))
1011      (simple-array-unsigned-byte-8
1012       :translation (simple-array (unsigned-byte 8) (*))
1013       :codes (#.sb!vm:simple-array-unsigned-byte-8-type)
1014       :direct-superclasses (vector simple-array)
1015       :inherits (vector simple-array array sequence
1016                  generic-vector generic-array mutable-sequence
1017                  mutable-collection generic-sequence collection))
1018      (simple-array-unsigned-byte-16
1019      :translation (simple-array (unsigned-byte 16) (*))
1020      :codes (#.sb!vm:simple-array-unsigned-byte-16-type)
1021      :direct-superclasses (vector simple-array)
1022      :inherits (vector simple-array array sequence
1023                 generic-vector generic-array mutable-sequence
1024                 mutable-collection generic-sequence collection))
1025      (simple-array-unsigned-byte-32
1026      :translation (simple-array (unsigned-byte 32) (*))
1027      :codes (#.sb!vm:simple-array-unsigned-byte-32-type)
1028      :direct-superclasses (vector simple-array)
1029      :inherits (vector simple-array array sequence
1030                 generic-vector generic-array mutable-sequence
1031                 mutable-collection generic-sequence collection))
1032      (simple-array-signed-byte-8
1033      :translation (simple-array (signed-byte 8) (*))
1034      :codes (#.sb!vm:simple-array-signed-byte-8-type)
1035      :direct-superclasses (vector simple-array)
1036      :inherits (vector simple-array array sequence
1037                 generic-vector generic-array mutable-sequence
1038                 mutable-collection generic-sequence collection))
1039      (simple-array-signed-byte-16
1040      :translation (simple-array (signed-byte 16) (*))
1041      :codes (#.sb!vm:simple-array-signed-byte-16-type)
1042      :direct-superclasses (vector simple-array)
1043      :inherits (vector simple-array array sequence
1044                 generic-vector generic-array mutable-sequence
1045                 mutable-collection generic-sequence collection))
1046      (simple-array-signed-byte-30
1047      :translation (simple-array (signed-byte 30) (*))
1048      :codes (#.sb!vm:simple-array-signed-byte-30-type)
1049      :direct-superclasses (vector simple-array)
1050      :inherits (vector simple-array array sequence
1051                 generic-vector generic-array mutable-sequence
1052                 mutable-collection generic-sequence collection))
1053      (simple-array-signed-byte-32
1054      :translation (simple-array (signed-byte 32) (*))
1055      :codes (#.sb!vm:simple-array-signed-byte-32-type)
1056      :direct-superclasses (vector simple-array)
1057      :inherits (vector simple-array array sequence
1058                 generic-vector generic-array mutable-sequence
1059                 mutable-collection generic-sequence collection))
1060      (simple-array-single-float
1061      :translation (simple-array single-float (*))
1062      :codes (#.sb!vm:simple-array-single-float-type)
1063      :direct-superclasses (vector simple-array)
1064      :inherits (vector simple-array array sequence
1065                 generic-vector generic-array mutable-sequence
1066                 mutable-collection generic-sequence collection))
1067      (simple-array-double-float
1068      :translation (simple-array double-float (*))
1069      :codes (#.sb!vm:simple-array-double-float-type)
1070      :direct-superclasses (vector simple-array)
1071      :inherits (vector simple-array array sequence
1072                 generic-vector generic-array mutable-sequence
1073                 mutable-collection generic-sequence collection))
1074     #!+long-float
1075     (simple-array-long-float
1076      :translation (simple-array long-float (*))
1077      :codes (#.sb!vm:simple-array-long-float-type)
1078      :direct-superclasses (vector simple-array)
1079      :inherits (vector simple-array array sequence
1080                 generic-vector generic-array mutable-sequence
1081                 mutable-collection generic-sequence collection))
1082     (simple-array-complex-single-float
1083      :translation (simple-array (complex single-float) (*))
1084      :codes (#.sb!vm:simple-array-complex-single-float-type)
1085      :direct-superclasses (vector simple-array)
1086      :inherits (vector simple-array array sequence
1087                 generic-vector generic-array mutable-sequence
1088                 mutable-collection generic-sequence collection))
1089     (simple-array-complex-double-float
1090      :translation (simple-array (complex double-float) (*))
1091      :codes (#.sb!vm:simple-array-complex-double-float-type)
1092      :direct-superclasses (vector simple-array)
1093      :inherits (vector simple-array array sequence
1094                 generic-vector generic-array mutable-sequence
1095                 mutable-collection generic-sequence collection))
1096     #!+long-float
1097     (simple-array-complex-long-float
1098      :translation (simple-array (complex long-float) (*))
1099      :codes (#.sb!vm:simple-array-complex-long-float-type)
1100      :direct-superclasses (vector simple-array)
1101      :inherits (vector simple-array array sequence
1102                 generic-vector generic-array mutable-sequence
1103                 mutable-collection generic-sequence collection))
1104     (generic-string
1105      :state :read-only
1106      :inherits (mutable-sequence mutable-collection generic-sequence
1107                 collection))
1108     (string
1109      :translation string
1110      :codes (#.sb!vm:complex-string-type)
1111      :direct-superclasses (vector generic-string)
1112      :inherits (vector array sequence
1113                 generic-vector generic-array generic-string
1114                 mutable-sequence mutable-collection
1115                 generic-sequence collection))
1116     (simple-string
1117      :translation simple-string
1118      :codes (#.sb!vm:simple-string-type)
1119      :direct-superclasses (string simple-array)
1120      :inherits (string vector simple-array
1121                 array sequence
1122                 generic-string generic-vector generic-array mutable-sequence
1123                 mutable-collection generic-sequence collection))
1124     (list
1125      :translation (or cons (member nil))
1126      :inherits (sequence mutable-sequence mutable-collection
1127                 generic-sequence collection))
1128     (cons
1129      :codes (#.sb!vm:list-pointer-type)
1130      :translation cons
1131      :inherits (list sequence
1132                 mutable-sequence mutable-collection
1133                 generic-sequence collection))
1134     (null
1135      :translation (member nil)
1136      :inherits (list sequence
1137                 mutable-sequence mutable-collection
1138                 generic-sequence collection symbol)
1139      :direct-superclasses (list symbol))
1140     (generic-number :state :read-only)
1141     (number :translation number :inherits (generic-number))
1142     (complex
1143      :translation complex
1144      :inherits (number generic-number)
1145      :codes (#.sb!vm:complex-type))
1146     (complex-single-float
1147      :translation (complex single-float)
1148      :inherits (complex number generic-number)
1149      :codes (#.sb!vm:complex-single-float-type))
1150     (complex-double-float
1151      :translation (complex double-float)
1152      :inherits (complex number generic-number)
1153      :codes (#.sb!vm:complex-double-float-type))
1154     #!+long-float
1155     (complex-long-float
1156      :translation (complex long-float)
1157      :inherits (complex number generic-number)
1158      :codes (#.sb!vm:complex-long-float-type))
1159     (real :translation real :inherits (number generic-number))
1160     (float
1161      :translation float
1162      :inherits (real number generic-number))
1163     (single-float
1164      :translation single-float
1165      :inherits (float real number generic-number)
1166      :codes (#.sb!vm:single-float-type))
1167     (double-float
1168      :translation double-float
1169      :inherits (float real number generic-number)
1170      :codes (#.sb!vm:double-float-type))
1171     #!+long-float
1172     (long-float
1173      :translation long-float
1174      :inherits (float real number generic-number)
1175      :codes (#.sb!vm:long-float-type))
1176     (rational
1177      :translation rational
1178      :inherits (real number generic-number))
1179     (ratio
1180      :translation (and rational (not integer))
1181      :inherits (rational real number generic-number)
1182      :codes (#.sb!vm:ratio-type))
1183     (integer
1184      :translation integer
1185      :inherits (rational real number generic-number))
1186     (fixnum
1187      :translation (integer #.sb!vm:*target-most-negative-fixnum*
1188                            #.sb!vm:*target-most-positive-fixnum*)
1189      :inherits (integer rational real number
1190                 generic-number)
1191      :codes (#.sb!vm:even-fixnum-type #.sb!vm:odd-fixnum-type))
1192     (bignum
1193      :translation (and integer (not fixnum))
1194      :inherits (integer rational real number
1195                 generic-number)
1196      :codes (#.sb!vm:bignum-type))
1197     (stream
1198      :state :read-only
1199      :depth 3
1200      :inherits (instance)))))
1201
1202 ;;; comment from CMU CL:
1203 ;;;   See also type-init.lisp where we finish setting up the
1204 ;;;   translations for built-in types.
1205 (!cold-init-forms
1206   (dolist (x *built-in-classes*)
1207     #-sb-xc-host (/show0 "at head of loop over *BUILT-IN-CLASSES*")
1208     (destructuring-bind
1209         (name &key
1210               (translation nil trans-p)
1211               inherits
1212               codes
1213               enumerable
1214               state
1215               depth
1216               (hierarchical-p t) ; might be modified below
1217               (direct-superclasses (if inherits
1218                                      (list (car inherits))
1219                                      '(t))))
1220         x
1221       (declare (ignore codes state translation))
1222       (let ((inherits-list (if (eq name t)
1223                                ()
1224                                (cons t (reverse inherits))))
1225             (class (make-built-in-class
1226                     :enumerable enumerable
1227                     :name name
1228                     :translation (if trans-p :initializing nil)
1229                     :direct-superclasses
1230                     (if (eq name t)
1231                       nil
1232                       (mapcar #'sb!xc:find-class direct-superclasses)))))
1233         (setf (info :type :kind name) :primitive
1234               (class-cell-class (find-class-cell name)) class)
1235         (unless trans-p
1236           (setf (info :type :builtin name) class))
1237         (let* ((inherits-vector
1238                 (map 'simple-vector
1239                      (lambda (x)
1240                        (let ((super-layout
1241                               (class-layout (sb!xc:find-class x))))
1242                          (when (minusp (layout-depthoid super-layout))
1243                            (setf hierarchical-p nil))
1244                          super-layout))
1245                      inherits-list))
1246                (depthoid (if hierarchical-p
1247                            (or depth (length inherits-vector))
1248                            -1)))
1249           (register-layout
1250            (find-and-init-or-check-layout name
1251                                           0
1252                                           inherits-vector
1253                                           depthoid)
1254            :invalidate nil)))))
1255   (/show0 "done with loop over *BUILT-IN-CLASSES*"))
1256
1257 ;;; Define temporary PCL STANDARD-CLASSes. These will be set up
1258 ;;; correctly and the Lisp layout replaced by a PCL wrapper after PCL
1259 ;;; is loaded and the class defined.
1260 (!cold-init-forms
1261   (/show0 "about to define temporary STANDARD-CLASSes")
1262   (dolist (x '(;; Why is STREAM duplicated in this list? Because, when
1263                ;; the inherits-vector of FUNDAMENTAL-STREAM is set up,
1264                ;; a vector containing the elements of the list below,
1265                ;; i.e. '(T INSTANCE STREAM STREAM), is created, and
1266                ;; this is what the function ORDER-LAYOUT-INHERITS
1267                ;; would do, too.
1268                ;;
1269                ;; So, the purpose is to guarantee a valid layout for
1270                ;; the FUNDAMENTAL-STREAM class, matching what
1271                ;; ORDER-LAYOUT-INHERITS would do.
1272                ;; ORDER-LAYOUT-INHERITS would place STREAM at index 3
1273                ;; in the INHERITS(-VECTOR). Index 2 would not be
1274                ;; filled, so STREAM is duplicated there (as
1275                ;; ORDER-LAYOUTS-INHERITS would do). Maybe the
1276                ;; duplicate definition could be removed (removing a
1277                ;; STREAM element), because FUNDAMENTAL-STREAM is
1278                ;; redefined after PCL is set up, anyway. But to play
1279                ;; it safely, we define the class with a valid INHERITS
1280                ;; vector.
1281                (fundamental-stream (t instance stream stream))))
1282     (/show0 "defining temporary STANDARD-CLASS")
1283     (let* ((name (first x))
1284            (inherits-list (second x))
1285            (class (make-standard-class :name name))
1286            (class-cell (find-class-cell name)))
1287       (setf (class-cell-class class-cell) class
1288             (info :type :class name) class-cell
1289             (info :type :kind name) :instance)
1290       (let ((inherits (map 'simple-vector
1291                            (lambda (x)
1292                              (class-layout (sb!xc:find-class x)))
1293                            inherits-list)))
1294         #-sb-xc-host (/show0 "INHERITS=..") #-sb-xc-host (/hexstr inherits)
1295         (register-layout (find-and-init-or-check-layout name 0 inherits -1)
1296                          :invalidate nil))))
1297   (/show0 "done defining temporary STANDARD-CLASSes"))
1298
1299 ;;; Now that we have set up the class heterarchy, seal the sealed
1300 ;;; classes. This must be done after the subclasses have been set up.
1301 (!cold-init-forms
1302   (dolist (x *built-in-classes*)
1303     (destructuring-bind (name &key (state :sealed) &allow-other-keys) x
1304       (setf (class-state (sb!xc:find-class name)) state))))
1305 \f
1306 ;;;; class definition/redefinition
1307
1308 ;;; This is to be called whenever we are altering a class.
1309 (defun modify-class (class)
1310   (clear-type-caches)
1311   (when (member (class-state class) '(:read-only :frozen))
1312     ;; FIXME: This should probably be CERROR.
1313     (warn "making ~(~A~) class ~S writable"
1314           (class-state class)
1315           (sb!xc:class-name class))
1316     (setf (class-state class) nil)))
1317
1318 ;;; Mark LAYOUT as invalid. Setting DEPTHOID -1 helps cause unsafe
1319 ;;; structure type tests to fail. Remove class from all superclasses
1320 ;;; too (might not be registered, so might not be in subclasses of the
1321 ;;; nominal superclasses.)
1322 (defun invalidate-layout (layout)
1323   (declare (type layout layout))
1324   (setf (layout-invalid layout) t
1325         (layout-depthoid layout) -1)
1326   (let ((inherits (layout-inherits layout))
1327         (class (layout-class layout)))
1328     (modify-class class)
1329     (dotimes (i (length inherits)) ; FIXME: DOVECTOR
1330       (let* ((super (svref inherits i))
1331              (subs (class-subclasses (layout-class super))))
1332         (when subs
1333           (remhash class subs)))))
1334   (values))
1335 \f
1336 ;;;; cold loading initializations
1337
1338 ;;; FIXME: It would be good to arrange for this to be called when the
1339 ;;; cross-compiler is being built, not just when the target Lisp is
1340 ;;; being cold loaded. Perhaps this could be moved to its own file
1341 ;;; late in the stems-and-flags.lisp-expr sequence, and be put in
1342 ;;; !COLD-INIT-FORMS there?
1343 (defun !class-finalize ()
1344   (dohash (name layout *forward-referenced-layouts*)
1345     (let ((class (sb!xc:find-class name nil)))
1346       (cond ((not class)
1347              (setf (layout-class layout) (make-undefined-class name)))
1348             ((eq (class-layout class) layout)
1349              (remhash name *forward-referenced-layouts*))
1350             (t
1351              ;; FIXME: ERROR?
1352              (warn "something strange with forward layout for ~S:~%  ~S"
1353                    name
1354                    layout))))))
1355
1356 ;;; a vector that maps type codes to layouts, used for quickly finding
1357 ;;; the layouts of built-in classes
1358 (defvar *built-in-class-codes*) ; initialized in cold load
1359 (declaim (type simple-vector *built-in-class-codes*))
1360
1361 (!cold-init-forms
1362   #-sb-xc-host (/show0 "about to set *BUILT-IN-CLASS-CODES*")
1363   (setq *built-in-class-codes*
1364         (let* ((initial-element
1365                 (locally
1366                   ;; KLUDGE: There's a FIND-CLASS DEFTRANSFORM for
1367                   ;; constant class names which creates fast but
1368                   ;; non-cold-loadable, non-compact code. In this
1369                   ;; context, we'd rather have compact, cold-loadable
1370                   ;; code. -- WHN 19990928
1371                   (declare (notinline sb!xc:find-class))
1372                   (class-layout (sb!xc:find-class 'random-class))))
1373                (res (make-array 256 :initial-element initial-element)))
1374           (dolist (x *built-in-classes* res)
1375             (destructuring-bind (name &key codes &allow-other-keys)
1376                                 x
1377               (let ((layout (class-layout (sb!xc:find-class name))))
1378                 (dolist (code codes)
1379                   (setf (svref res code) layout)))))))
1380   #-sb-xc-host (/show0 "done setting *BUILT-IN-CLASS-CODES*"))
1381 \f
1382 (!defun-from-collected-cold-init-forms !classes-cold-init)