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