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