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