Initial revision
[sbcl.git] / src / pcl / braid.lisp
1 ;;;; bootstrapping the meta-braid
2 ;;;;
3 ;;;; The code in this file takes the early definitions that have been saved
4 ;;;; up and actually builds those class objects. This work is largely driven
5 ;;;; off of those class definitions, but the fact that STANDARD-CLASS is the
6 ;;;; class of all metaclasses in the braid is built into this code pretty
7 ;;;; deeply.
8
9 ;;;; This software is part of the SBCL system. See the README file for
10 ;;;; more information.
11
12 ;;;; This software is derived from software originally released by Xerox
13 ;;;; Corporation. Copyright and release statements follow. Later modifications
14 ;;;; to the software are in the public domain and are provided with
15 ;;;; absolutely no warranty. See the COPYING and CREDITS files for more
16 ;;;; information.
17
18 ;;;; copyright information from original PCL sources:
19 ;;;;
20 ;;;; Copyright (c) 1985, 1986, 1987, 1988, 1989, 1990 Xerox Corporation.
21 ;;;; All rights reserved.
22 ;;;;
23 ;;;; Use and copying of this software and preparation of derivative works based
24 ;;;; upon this software are permitted. Any distribution of this software or
25 ;;;; derivative works must comply with all applicable United States export
26 ;;;; control laws.
27 ;;;;
28 ;;;; This software is made available AS IS, and Xerox Corporation makes no
29 ;;;; warranty about the software, its performance or its conformity to any
30 ;;;; specification.
31
32 (in-package "SB-PCL")
33
34 (sb-int:file-comment
35   "$Header$")
36 \f
37 (defun allocate-standard-instance (wrapper
38                                    &optional (slots-init nil slots-init-p))
39   (let ((instance (%%allocate-instance--class))
40         (no-of-slots (wrapper-no-of-instance-slots wrapper)))
41     (setf (std-instance-wrapper instance) wrapper)
42     (setf (std-instance-slots instance)
43           (cond (slots-init-p
44                  ;; Inline the slots vector allocation and initialization.
45                  (let ((slots (make-array no-of-slots :initial-element 0)))
46                    (do ((rem-slots slots-init (rest rem-slots))
47                         (i 0 (1+ i)))
48                        ((>= i no-of-slots)) ;endp rem-slots))
49                      (declare (list rem-slots)
50                               (type sb-kernel:index i))
51                      (setf (aref slots i) (first rem-slots)))
52                    slots))
53                 (t
54                  (make-array no-of-slots
55                              :initial-element sb-pcl::*slot-unbound*))))
56     instance))
57
58 (defmacro allocate-funcallable-instance-slots (wrapper &optional
59                                                        slots-init-p slots-init)
60   `(let ((no-of-slots (wrapper-no-of-instance-slots ,wrapper)))
61      ,(if slots-init-p
62           `(if ,slots-init-p
63                (make-array no-of-slots :initial-contents ,slots-init)
64                (make-array no-of-slots :initial-element *slot-unbound*))
65           `(make-array no-of-slots :initial-element *slot-unbound*))))
66
67 (defun allocate-funcallable-instance (wrapper &optional
68                                               (slots-init nil slots-init-p))
69   (let ((fin (allocate-funcallable-instance-1)))
70     (set-funcallable-instance-function
71      fin
72      #'(sb-kernel:instance-lambda (&rest args)
73          (declare (ignore args))
74          (error "The function of the funcallable-instance ~S has not been set."
75                 fin)))
76     (setf (fsc-instance-wrapper fin) wrapper
77           (fsc-instance-slots fin) (allocate-funcallable-instance-slots
78                                     wrapper slots-init-p slots-init))
79     fin))
80
81 (defun allocate-structure-instance (wrapper &optional
82                                             (slots-init nil slots-init-p))
83   (let* ((class (wrapper-class wrapper))
84          (constructor (class-defstruct-constructor class)))
85     (if constructor
86         (let ((instance (funcall constructor))
87               (slots (class-slots class)))
88           (when slots-init-p
89             (dolist (slot slots)
90               (setf (slot-value-using-class class instance slot)
91                     (pop slots-init))))
92           instance)
93         (error "can't allocate an instance of class ~S" (class-name class)))))
94 \f
95 ;;;; BOOTSTRAP-META-BRAID
96 ;;;;
97 ;;;; This function builds the base metabraid from the early class definitions.
98 ;;;;
99 ;;;; FIXME: This, like lotso the other stuff in PCL, is not needed in target
100 ;;;; Lisp, only at bootstrap time. Perhaps we should do something kludgy like
101 ;;;; putting a special character (#\$, perhaps) at the beginning of each
102 ;;;; needed-only-at-bootstrap-time symbol and then UNINTERN them all once we're
103 ;;;; done bootstrapping?
104
105 (defmacro initial-classes-and-wrappers (&rest classes)
106   `(progn
107      ,@(mapcar #'(lambda (class)
108                    (let ((wr (intern (format nil "~A-WRAPPER" class)
109                                      *pcl-package*)))
110                      `(setf ,wr ,(if (eq class 'standard-generic-function)
111                                      '*sgf-wrapper*
112                                      `(boot-make-wrapper
113                                        (early-class-size ',class)
114                                        ',class))
115                             ,class (allocate-standard-instance
116                                     ,(if (eq class 'standard-generic-function)
117                                          'funcallable-standard-class-wrapper
118                                          'standard-class-wrapper))
119                             (wrapper-class ,wr) ,class
120                             (find-class ',class) ,class)))
121               classes)))
122
123 (defun bootstrap-meta-braid ()
124   (let* ((name 'class)
125          (predicate-name (make-type-predicate-name name)))
126     (setf (gdefinition predicate-name)
127           #'(lambda (x) (declare (ignore x)) t))
128     (do-satisfies-deftype name predicate-name))
129   (let* ((*create-classes-from-internal-structure-definitions-p* nil)
130          std-class-wrapper std-class
131          standard-class-wrapper standard-class
132          funcallable-standard-class-wrapper funcallable-standard-class
133          slot-class-wrapper slot-class
134          built-in-class-wrapper built-in-class
135          structure-class-wrapper structure-class
136          standard-direct-slot-definition-wrapper
137          standard-direct-slot-definition
138          standard-effective-slot-definition-wrapper
139          standard-effective-slot-definition
140          class-eq-specializer-wrapper class-eq-specializer
141          standard-generic-function-wrapper standard-generic-function)
142     (initial-classes-and-wrappers
143      standard-class funcallable-standard-class
144      slot-class built-in-class structure-class std-class
145      standard-direct-slot-definition standard-effective-slot-definition
146      class-eq-specializer standard-generic-function)
147     ;; First, make a class metaobject for each of the early classes. For
148     ;; each metaobject we also set its wrapper. Except for the class T,
149     ;; the wrapper is always that of STANDARD-CLASS.
150     (dolist (definition *early-class-definitions*)
151       (let* ((name (ecd-class-name definition))
152              (meta (ecd-metaclass definition))
153              (wrapper (ecase meta
154                         (slot-class slot-class-wrapper)
155                         (std-class std-class-wrapper)
156                         (standard-class standard-class-wrapper)
157                         (funcallable-standard-class
158                          funcallable-standard-class-wrapper)
159                         (built-in-class built-in-class-wrapper)
160                         (structure-class structure-class-wrapper)))
161              (class (or (find-class name nil)
162                         (allocate-standard-instance wrapper))))
163         (when (or (eq meta 'standard-class)
164                   (eq meta 'funcallable-standard-class))
165           (inform-type-system-about-std-class name))
166         (setf (find-class name) class)))
167     (dolist (definition *early-class-definitions*)
168       (let ((name (ecd-class-name definition))
169             (meta (ecd-metaclass definition))
170             (source (ecd-source definition))
171             (direct-supers (ecd-superclass-names definition))
172             (direct-slots  (ecd-canonical-slots definition))
173             (other-initargs (ecd-other-initargs definition)))
174         (let ((direct-default-initargs
175                (getf other-initargs :direct-default-initargs)))
176           (multiple-value-bind (slots cpl default-initargs direct-subclasses)
177               (early-collect-inheritance name)
178             (let* ((class (find-class name))
179                    (wrapper (cond ((eq class slot-class)
180                                    slot-class-wrapper)
181                                   ((eq class std-class)
182                                    std-class-wrapper)
183                                   ((eq class standard-class)
184                                    standard-class-wrapper)
185                                   ((eq class funcallable-standard-class)
186                                    funcallable-standard-class-wrapper)
187                                   ((eq class standard-direct-slot-definition)
188                                    standard-direct-slot-definition-wrapper)
189                                   ((eq class
190                                        standard-effective-slot-definition)
191                                    standard-effective-slot-definition-wrapper)
192                                   ((eq class built-in-class)
193                                    built-in-class-wrapper)
194                                   ((eq class structure-class)
195                                    structure-class-wrapper)
196                                   ((eq class class-eq-specializer)
197                                    class-eq-specializer-wrapper)
198                                   ((eq class standard-generic-function)
199                                    standard-generic-function-wrapper)
200                                   (t
201                                    (boot-make-wrapper (length slots) name))))
202                    (proto nil))
203               (when (eq name 't) (setq *the-wrapper-of-t* wrapper))
204               (set (intern (format nil "*THE-CLASS-~A*" (symbol-name name))
205                            *pcl-package*)
206                    class)
207               (dolist (slot slots)
208                 (unless (eq (getf slot :allocation :instance) :instance)
209                   (error "Slot allocation ~S is not supported in bootstrap.")))
210
211               (when (typep wrapper 'wrapper)
212                 (setf (wrapper-instance-slots-layout wrapper)
213                       (mapcar #'canonical-slot-name slots))
214                 (setf (wrapper-class-slots wrapper)
215                       ()))
216
217               (setq proto (if (eq meta 'funcallable-standard-class)
218                               (allocate-funcallable-instance wrapper)
219                               (allocate-standard-instance wrapper)))
220
221               (setq direct-slots
222                     (bootstrap-make-slot-definitions
223                      name class direct-slots
224                      standard-direct-slot-definition-wrapper nil))
225               (setq slots
226                     (bootstrap-make-slot-definitions
227                      name class slots
228                      standard-effective-slot-definition-wrapper t))
229
230               (case meta
231                 ((std-class standard-class funcallable-standard-class)
232                  (bootstrap-initialize-class
233                   meta
234                   class name class-eq-specializer-wrapper source
235                   direct-supers direct-subclasses cpl wrapper proto
236                   direct-slots slots direct-default-initargs default-initargs))
237                 (built-in-class         ; *the-class-t*
238                  (bootstrap-initialize-class
239                   meta
240                   class name class-eq-specializer-wrapper source
241                   direct-supers direct-subclasses cpl wrapper proto))
242                 (slot-class             ; *the-class-slot-object*
243                  (bootstrap-initialize-class
244                   meta
245                   class name class-eq-specializer-wrapper source
246                   direct-supers direct-subclasses cpl wrapper proto))
247                 (structure-class        ; *the-class-structure-object*
248                  (bootstrap-initialize-class
249                   meta
250                   class name class-eq-specializer-wrapper source
251                   direct-supers direct-subclasses cpl wrapper))))))))
252
253     (let* ((smc-class (find-class 'standard-method-combination))
254            (smc-wrapper (bootstrap-get-slot 'standard-class
255                                             smc-class
256                                             'wrapper))
257            (smc (allocate-standard-instance smc-wrapper)))
258       (flet ((set-slot (name value)
259                (bootstrap-set-slot 'standard-method-combination
260                                    smc
261                                    name
262                                    value)))
263         (set-slot 'source *load-truename*)
264         (set-slot 'type 'standard)
265         (set-slot 'documentation "The standard method combination.")
266         (set-slot 'options ()))
267       (setq *standard-method-combination* smc))))
268
269 ;;; Initialize a class metaobject.
270 ;;;
271 ;;; FIXME: This and most stuff in this file is probably only needed at init
272 ;;; time.
273 (defun bootstrap-initialize-class
274        (metaclass-name class name
275         class-eq-wrapper source direct-supers direct-subclasses cpl wrapper
276         &optional
277         proto direct-slots slots direct-default-initargs default-initargs)
278   (flet ((classes (names) (mapcar #'find-class names))
279          (set-slot (slot-name value)
280            (bootstrap-set-slot metaclass-name class slot-name value)))
281     (set-slot 'name name)
282     (set-slot 'source source)
283     (set-slot 'type (if (eq class (find-class 't))
284                         t
285                         `(class ,class)))
286     (set-slot 'class-eq-specializer
287               (let ((spec (allocate-standard-instance class-eq-wrapper)))
288                 (bootstrap-set-slot 'class-eq-specializer spec 'type
289                                     `(class-eq ,class))
290                 (bootstrap-set-slot 'class-eq-specializer spec 'object
291                                     class)
292                 spec))
293     (set-slot 'class-precedence-list (classes cpl))
294     (set-slot 'can-precede-list (classes (cdr cpl)))
295     (set-slot 'incompatible-superclass-list nil)
296     (set-slot 'direct-superclasses (classes direct-supers))
297     (set-slot 'direct-subclasses (classes direct-subclasses))
298     (set-slot 'direct-methods (cons nil nil))
299     (set-slot 'wrapper wrapper)
300     (set-slot 'predicate-name (or (cadr (assoc name *early-class-predicates*))
301                                   (make-class-predicate-name name)))
302     (set-slot 'plist
303               `(,@(and direct-default-initargs
304                        `(direct-default-initargs ,direct-default-initargs))
305                 ,@(and default-initargs
306                        `(default-initargs ,default-initargs))))
307     (when (memq metaclass-name '(standard-class funcallable-standard-class
308                                  structure-class slot-class std-class))
309       (set-slot 'direct-slots direct-slots)
310       (set-slot 'slots slots)
311       (set-slot 'initialize-info nil))
312     (if (eq metaclass-name 'structure-class)
313         (let ((constructor-sym '|STRUCTURE-OBJECT class constructor|))
314           (set-slot 'predicate-name (or (cadr (assoc name
315                                                      *early-class-predicates*))
316                                         (make-class-predicate-name name)))
317           (set-slot 'defstruct-form
318                     `(defstruct (structure-object (:constructor
319                                                    ,constructor-sym))))
320           (set-slot 'defstruct-constructor constructor-sym)
321           (set-slot 'from-defclass-p t)
322           (set-slot 'plist nil)
323           (set-slot 'prototype (funcall constructor-sym)))
324         (set-slot 'prototype (or proto (allocate-standard-instance wrapper))))
325     class))
326
327 (defun bootstrap-make-slot-definitions (name class slots wrapper effective-p)
328   (let ((index -1))
329     (mapcar #'(lambda (slot)
330                 (incf index)
331                 (bootstrap-make-slot-definition
332                   name class slot wrapper effective-p index))
333             slots)))
334
335 (defun bootstrap-make-slot-definition
336     (name class slot wrapper effective-p index)
337   (let* ((slotd-class-name (if effective-p
338                                'standard-effective-slot-definition
339                                'standard-direct-slot-definition))
340          (slotd (allocate-standard-instance wrapper))
341          (slot-name (getf slot :name)))
342     (flet ((get-val (name) (getf slot name))
343            (set-val (name val)
344                     (bootstrap-set-slot slotd-class-name slotd name val)))
345       (set-val 'name     slot-name)
346       (set-val 'initform     (get-val :initform))
347       (set-val 'initfunction (get-val :initfunction))
348       (set-val 'initargs     (get-val :initargs))
349       (set-val 'readers      (get-val :readers))
350       (set-val 'writers      (get-val :writers))
351       (set-val 'allocation   :instance)
352       (set-val 'type     (or (get-val :type) t))
353       (set-val 'documentation (or (get-val :documentation) ""))
354       (set-val 'class   class)
355       (when effective-p
356         (set-val 'location index)
357         (let ((fsc-p nil))
358           (set-val 'reader-function (make-optimized-std-reader-method-function
359                                      fsc-p slot-name index))
360           (set-val 'writer-function (make-optimized-std-writer-method-function
361                                      fsc-p slot-name index))
362           (set-val 'boundp-function (make-optimized-std-boundp-method-function
363                                      fsc-p slot-name index)))
364         (set-val 'accessor-flags 7)
365         (let ((table (or (gethash slot-name *name->class->slotd-table*)
366                          (setf (gethash slot-name *name->class->slotd-table*)
367                                (make-hash-table :test 'eq :size 5)))))
368           (setf (gethash class table) slotd)))
369       (when (and (eq name 'standard-class)
370                  (eq slot-name 'slots) effective-p)
371         (setq *the-eslotd-standard-class-slots* slotd))
372       (when (and (eq name 'funcallable-standard-class)
373                  (eq slot-name 'slots) effective-p)
374         (setq *the-eslotd-funcallable-standard-class-slots* slotd))
375       slotd)))
376
377 (defun bootstrap-accessor-definitions (early-p)
378   (let ((*early-p* early-p))
379     (dolist (definition *early-class-definitions*)
380       (let ((name (ecd-class-name definition))
381             (meta (ecd-metaclass definition)))
382         (unless (eq meta 'built-in-class)
383           (let ((direct-slots  (ecd-canonical-slots definition)))
384             (dolist (slotd direct-slots)
385               (let ((slot-name (getf slotd :name))
386                     (readers (getf slotd :readers))
387                     (writers (getf slotd :writers)))
388                 (bootstrap-accessor-definitions1
389                  name
390                  slot-name
391                  readers
392                  writers
393                  nil)
394                 (bootstrap-accessor-definitions1
395                  'slot-object
396                  slot-name
397                  (list (slot-reader-symbol slot-name))
398                  (list (slot-writer-symbol slot-name))
399                  (list (slot-boundp-symbol slot-name)))))))))))
400
401 (defun bootstrap-accessor-definition (class-name accessor-name slot-name type)
402   (multiple-value-bind (accessor-class make-method-function arglist specls doc)
403       (ecase type
404         (reader (values 'standard-reader-method
405                         #'make-std-reader-method-function
406                         (list class-name)
407                         (list class-name)
408                         "automatically generated reader method"))
409         (writer (values 'standard-writer-method
410                         #'make-std-writer-method-function
411                         (list 'new-value class-name)
412                         (list 't class-name)
413                         "automatically generated writer method"))
414         (boundp (values 'standard-boundp-method
415                         #'make-std-boundp-method-function
416                         (list class-name)
417                         (list class-name)
418                         "automatically generated boundp method")))
419     (let ((gf (ensure-generic-function accessor-name)))
420       (if (find specls (early-gf-methods gf)
421                 :key #'early-method-specializers
422                 :test 'equal)
423           (unless (assoc accessor-name *generic-function-fixups*
424                          :test #'equal)
425             (update-dfun gf))
426           (add-method gf
427                       (make-a-method accessor-class
428                                      ()
429                                      arglist specls
430                                      (funcall make-method-function
431                                               class-name slot-name)
432                                      doc
433                                      slot-name))))))
434
435 (defun bootstrap-accessor-definitions1 (class-name
436                                         slot-name
437                                         readers
438                                         writers
439                                         boundps)
440   (flet ((do-reader-definition (reader)
441            (bootstrap-accessor-definition class-name
442                                           reader
443                                           slot-name
444                                           'reader))
445          (do-writer-definition (writer)
446            (bootstrap-accessor-definition class-name
447                                           writer
448                                           slot-name
449                                           'writer))
450          (do-boundp-definition (boundp)
451            (bootstrap-accessor-definition class-name
452                                           boundp
453                                           slot-name
454                                           'boundp)))
455     (dolist (reader readers) (do-reader-definition reader))
456     (dolist (writer writers) (do-writer-definition writer))
457     (dolist (boundp boundps) (do-boundp-definition boundp))))
458
459 (defun bootstrap-class-predicates (early-p)
460   (let ((*early-p* early-p))
461     (dolist (definition *early-class-definitions*)
462       (let* ((name (ecd-class-name definition))
463              (class (find-class name)))
464         (setf (find-class-predicate name)
465               (make-class-predicate class (class-predicate-name class)))))))
466
467 (defun bootstrap-built-in-classes ()
468
469   ;; First make sure that all the supers listed in
470   ;; *BUILT-IN-CLASS-LATTICE* are themselves defined by
471   ;; *BUILT-IN-CLASS-LATTICE*. This is just to check for typos and
472   ;; other sorts of brainos.
473   (dolist (e *built-in-classes*)
474     (dolist (super (cadr e))
475       (unless (or (eq super 't)
476                   (assq super *built-in-classes*))
477         (error "in *BUILT-IN-CLASSES*: ~S has ~S as a super,~%~
478                 but ~S is not itself a class in *BUILT-IN-CLASSES*."
479                (car e) super super))))
480
481   ;; In the first pass, we create a skeletal object to be bound to the
482   ;; class name.
483   (let* ((built-in-class (find-class 'built-in-class))
484          (built-in-class-wrapper (class-wrapper built-in-class)))
485     (dolist (e *built-in-classes*)
486       (let ((class (allocate-standard-instance built-in-class-wrapper)))
487         (setf (find-class (car e)) class))))
488
489   ;; In the second pass, we initialize the class objects.
490   (let ((class-eq-wrapper (class-wrapper (find-class 'class-eq-specializer))))
491     (dolist (e *built-in-classes*)
492       (destructuring-bind (name supers subs cpl prototype) e
493         (let* ((class (find-class name))
494                (lclass (cl:find-class name))
495                (wrapper (sb-kernel:class-layout lclass)))
496           (set (get-built-in-class-symbol name) class)
497           (set (get-built-in-wrapper-symbol name) wrapper)
498           (setf (sb-kernel:class-pcl-class lclass) class)
499
500           (bootstrap-initialize-class 'built-in-class class
501                                       name class-eq-wrapper nil
502                                       supers subs
503                                       (cons name cpl)
504                                       wrapper prototype)))))
505
506   (dolist (e *built-in-classes*)
507     (let* ((name (car e))
508            (class (find-class name)))
509       (setf (find-class-predicate name)
510             (make-class-predicate class (class-predicate-name class))))))
511 \f
512 (defmacro wrapper-of-macro (x)
513   `(sb-kernel:layout-of ,x))
514
515 (defun class-of (x)
516   (wrapper-class* (wrapper-of-macro x)))
517
518 ;;; FIXME: We probably don't need both WRAPPER-OF and WRAPPER-OF-MACRO.
519 #-sb-fluid (declaim (inline wrapper-of))
520 (defun wrapper-of (x)
521   (wrapper-of-macro x))
522
523 (defvar *find-structure-class* nil)
524
525 (defun eval-form (form)
526   #'(lambda () (eval form)))
527
528 (defun slot-initargs-from-structure-slotd (slotd)
529   `(:name ,(structure-slotd-name slotd)
530     :defstruct-accessor-symbol ,(structure-slotd-accessor-symbol slotd)
531     :internal-reader-function ,(structure-slotd-reader-function slotd)
532     :internal-writer-function ,(structure-slotd-writer-function slotd)
533     :type ,(or (structure-slotd-type slotd) t)
534     :initform ,(structure-slotd-init-form slotd)
535     :initfunction ,(eval-form (structure-slotd-init-form slotd))))
536
537 (defun find-structure-class (symbol)
538   (if (structure-type-p symbol)
539       (unless (eq *find-structure-class* symbol)
540         (let ((*find-structure-class* symbol))
541           (ensure-class symbol
542                         :metaclass 'structure-class
543                         :name symbol
544                         :direct-superclasses
545                         (cond ;; Handle our CMU-CL-ish structure-based
546                               ;; conditions.
547                               ((cl:subtypep symbol 'condition)
548                                (mapcar #'cl:class-name
549                                        (sb-kernel:class-direct-superclasses
550                                         (cl:find-class symbol))))
551                               ;; a hack to add the STREAM class as a
552                               ;; mixin to the LISP-STREAM class.
553                               ((eq symbol 'sb-sys:lisp-stream)
554                                '(structure-object stream))
555                               ((structure-type-included-type-name symbol)
556                                (list (structure-type-included-type-name
557                                       symbol))))
558                         :direct-slots
559                         (mapcar #'slot-initargs-from-structure-slotd
560                                 (structure-type-slot-description-list
561                                  symbol)))))
562       (error "~S is not a legal structure class name." symbol)))
563 \f
564 (defun method-function-returning-nil (args next-methods)
565   (declare (ignore args next-methods))
566   nil)
567
568 (defun method-function-returning-t (args next-methods)
569   (declare (ignore args next-methods))
570   t)
571
572 (defun make-class-predicate (class name)
573   (let* ((gf (ensure-generic-function name))
574          (mlist (if (eq *boot-state* 'complete)
575                     (generic-function-methods gf)
576                     (early-gf-methods gf))))
577     (unless mlist
578       (unless (eq class *the-class-t*)
579         (let* ((default-method-function #'method-function-returning-nil)
580                (default-method-initargs (list :function
581                                               default-method-function))
582                (default-method (make-a-method 'standard-method
583                                               ()
584                                               (list 'object)
585                                               (list *the-class-t*)
586                                               default-method-initargs
587                                               "class predicate default method")))
588           (setf (method-function-get default-method-function :constant-value)
589                 nil)
590           (add-method gf default-method)))
591       (let* ((class-method-function #'method-function-returning-t)
592              (class-method-initargs (list :function
593                                           class-method-function))
594              (class-method (make-a-method 'standard-method
595                                           ()
596                                           (list 'object)
597                                           (list class)
598                                           class-method-initargs
599                                           "class predicate class method")))
600         (setf (method-function-get class-method-function :constant-value) t)
601         (add-method gf class-method)))
602     gf))
603
604 ;;; Set the inherits from CPL, and register the layout. This actually
605 ;;; installs the class in the Lisp type system.
606 (defun update-lisp-class-layout (class layout)
607   (let ((lclass (sb-kernel:layout-class layout)))
608     (unless (eq (sb-kernel:class-layout lclass) layout)
609       (setf (sb-kernel:layout-inherits layout)
610             (map 'vector #'class-wrapper
611                  (reverse (rest (class-precedence-list class)))))
612       (sb-kernel:register-layout layout :invalidate nil)
613
614       ;; Subclasses of formerly forward-referenced-class may be unknown
615       ;; to CL:FIND-CLASS and also anonymous. This functionality moved
616       ;; here from (SETF FIND-CLASS).
617       (let ((name (class-name class)))
618         (setf (cl:find-class name) lclass
619               ;; FIXME: It's nasty to use double colons. Perhaps the
620               ;; best way to fix this is not to export CLASS-%NAME
621               ;; from SB-KERNEL, but instead to move the whole
622               ;; UPDATE-LISP-CLASS-LAYOUT function to SB-KERNEL, and
623               ;; export it. (since it's also nasty for us to be
624               ;; reaching into %KERNEL implementation details my
625               ;; messing with raw CLASS-%NAME)
626               (sb-kernel::class-%name lclass) name)))))
627
628 (eval-when (:load-toplevel :execute)
629
630   (clrhash *find-class*)
631   (bootstrap-meta-braid)
632   (bootstrap-accessor-definitions t)
633   (bootstrap-class-predicates t)
634   (bootstrap-accessor-definitions nil)
635   (bootstrap-class-predicates nil)
636   (bootstrap-built-in-classes)
637
638   (sb-int:dohash (name x *find-class*)
639     (let* ((class (find-class-from-cell name x))
640            (layout (class-wrapper class))
641            (lclass (sb-kernel:layout-class layout))
642            (lclass-pcl-class (sb-kernel:class-pcl-class lclass))
643            (olclass (cl:find-class name nil)))
644       (if lclass-pcl-class
645           (assert (eq class lclass-pcl-class))
646           (setf (sb-kernel:class-pcl-class lclass) class))
647
648       (update-lisp-class-layout class layout)
649
650       (cond (olclass
651              (assert (eq lclass olclass)))
652             (t
653              (setf (cl:find-class name) lclass)))))
654
655   (setq *boot-state* 'braid)
656
657   ) ; EVAL-WHEN
658
659 (defmethod no-applicable-method (generic-function &rest args)
660   ;; FIXME: probably could be ERROR instead of CERROR
661   (cerror "Retry call to ~S."
662           "There is no matching method for the generic function ~S~@
663           when called with arguments ~S."
664           generic-function
665           args)
666   (apply generic-function args))