0.7.10.31:
[sbcl.git] / src / pcl / ctor.lisp
1 ;;;; This file contains the optimization machinery for make-instance.
2
3 ;;;; This software is part of the SBCL system. See the README file for
4 ;;;; more information.
5
6 ;;;; This software is derived from software originally released by
7 ;;;; Gerd Moellmann.  Copyright and release statements follow.  Later
8 ;;;; modifications to the software are in the public domain and are
9 ;;;; provided with absolutely no warranty.  See the COPYING and
10 ;;;; CREDITS files for more information.
11
12 ;;; Copyright (C) 2002 Gerd Moellmann <gerd.moellmann@t-online.de>
13 ;;; All rights reserved.
14 ;;;
15 ;;; Redistribution and use in source and binary forms, with or without
16 ;;; modification, are permitted provided that the following conditions
17 ;;; are met:
18 ;;;
19 ;;; 1. Redistributions of source code must retain the above copyright
20 ;;;    notice, this list of conditions and the following disclaimer.
21 ;;; 2. Redistributions in binary form must reproduce the above copyright
22 ;;;    notice, this list of conditions and the following disclaimer in the
23 ;;;    documentation and/or other materials provided with the distribution.
24 ;;; 3. The name of the author may not be used to endorse or promote
25 ;;;    products derived from this software without specific prior written
26 ;;;    permission.
27 ;;;
28 ;;; THIS SOFTWARE IS PROVIDED BY THE AUTHOR ``AS IS'' AND ANY EXPRESS
29 ;;; OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
30 ;;; WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
31 ;;; ARE DISCLAIMED.  IN NO EVENT SHALL THE AUTHOR OR CONTRIBUTORS BE
32 ;;; LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
33 ;;; CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT
34 ;;; OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR
35 ;;; BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF
36 ;;; LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
37 ;;; (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE
38 ;;; USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH
39 ;;; DAMAGE.
40
41 ;;; ***************
42 ;;; Overview  *****
43 ;;; ***************
44 ;;;
45 ;;; Compiler macro for MAKE-INSTANCE, and load-time generation of
46 ;;; optimized instance constructor functions.
47 ;;;
48 ;;; ********************
49 ;;; Entry Points  ******
50 ;;; ********************
51 ;;;
52 ;;; UPDATE-CTORS must be called when methods are added/removed,
53 ;;; classes are changed, etc., which affect instance creation.
54 ;;;
55 ;;; PRECOMPILE-CTORS can be called to precompile constructor functions
56 ;;; for classes whose definitions are known at the time the function
57 ;;; is called.
58
59 (in-package "SB-PCL")
60
61 ;;; ******************
62 ;;; Utilities  *******
63 ;;; ******************
64
65 (defun plist-keys (plist &key test)
66   (loop for (key . more) on plist by #'cddr
67         if (null more) do
68           (error "Not a property list: ~S" plist)
69         else if (or (null test) (funcall test key))
70           collect key))
71
72 (defun plist-values (plist &key test)
73   (loop for (key . more) on plist by #'cddr
74         if (null more) do
75           (error "Not a property list: ~S" plist)
76         else if (or (null test) (funcall test (car more)))
77           collect (car more)))
78
79 (defun constant-symbol-p (form)
80   (and (constantp form)
81        (let ((constant (eval form)))
82          (and (symbolp constant)
83               (not (null (symbol-package constant)))))))
84
85 \f
86 ;;; *****************
87 ;;; CTORS   *********
88 ;;; *****************
89 ;;;
90 ;;; Ctors are funcallable instances whose initial function is a
91 ;;; function computing an optimized constructor function when called.
92 ;;; When the optimized function is computed, the function of the
93 ;;; funcallable instance is set to it.
94 ;;;
95 (sb-kernel:!defstruct-with-alternate-metaclass ctor
96   :slot-names (function-name class-name class initargs)
97   :boa-constructor %make-ctor
98   :superclass-name pcl-funcallable-instance
99   :metaclass-name sb-kernel:random-pcl-class
100   :metaclass-constructor sb-kernel:make-random-pcl-class
101   :dd-type sb-kernel:funcallable-structure
102   :runtime-type-checks-p nil)
103
104 ;;; List of all defined ctors.
105
106 (defvar *all-ctors* ())
107
108 (defun make-ctor-parameter-list (ctor)
109   (plist-values (ctor-initargs ctor) :test (complement #'constantp)))
110
111 ;;;
112 ;;; Reset CTOR to use a default function that will compute an
113 ;;; optimized constructor function when called.
114 ;;;
115 (defun install-initial-constructor (ctor &key force-p)
116   (when (or force-p (ctor-class ctor))
117     (setf (ctor-class ctor) nil)
118     (setf (sb-kernel:funcallable-instance-fun ctor)
119           #'(sb-kernel:instance-lambda (&rest args)
120               (install-optimized-constructor ctor)
121               (apply ctor args)))
122     (setf (sb-kernel:%funcallable-instance-info ctor 1)
123           (ctor-function-name ctor))))
124
125 ;;;
126 ;;; Keep this a separate function for testing.
127 ;;;
128 (defun make-ctor-function-name (class-name initargs)
129   (let ((*package* *pcl-package*)
130         (*print-case* :upcase)
131         (*print-pretty* nil)
132         (*print-gensym* t))
133     (intern (format nil "CTOR ~S::~S ~S ~S"
134                     (package-name (symbol-package class-name))
135                     (symbol-name class-name)
136                     (plist-keys initargs)
137                     (plist-values initargs :test #'constantp))
138             *pcl-package*)))
139
140 ;;;
141 ;;; Keep this a separate function for testing.
142 ;;;
143 (defun ensure-ctor (function-name class-name initargs)
144   (unless (fboundp function-name)
145     (make-ctor function-name class-name initargs)))
146
147 ;;;
148 ;;; Keep this a separate function for testing.
149 ;;;
150 (defun make-ctor (function-name class-name initargs)
151   (let ((ctor (%make-ctor function-name class-name nil initargs)))
152     (push ctor *all-ctors*)
153     (setf (symbol-function function-name) ctor)
154     (install-initial-constructor ctor :force-p t)
155     ctor))
156
157 \f
158 ;;; ***********************************************
159 ;;; Compile-Time Expansion of MAKE-INSTANCE *******
160 ;;; ***********************************************
161
162 (define-compiler-macro make-instance (&whole form &rest args)
163   (declare (ignore args))
164   (or (make-instance->constructor-call form)
165       form))
166
167 (defun make-instance->constructor-call (form)
168   (destructuring-bind (fn class-name &rest args) form
169     (declare (ignore fn))
170     (flet (;;
171            ;; Return the name of parameter number I of a constructor
172            ;; function.
173            (parameter-name (i)
174              (let ((ps #(.p0. .p1. .p2. .p3. .p4. .p5.)))
175                (if (array-in-bounds-p ps i)
176                    (aref ps i)
177                    (intern (format nil ".P~D." i) *pcl-package*))))
178            ;;
179            ;; Check if CLASS-NAME is a constant symbol.  Give up if
180            ;; not.
181            (check-class ()
182              (unless (and class-name (constant-symbol-p class-name))
183                (return-from make-instance->constructor-call nil)))
184            ;;
185            ;; Check if ARGS are suitable for an optimized constructor.
186            ;; Return NIL from the outer function if not.
187            (check-args ()
188              (loop for (key . more) on args by #'cddr do
189                      (when (or (null more)
190                                (not (constant-symbol-p key))
191                                (eq :allow-other-keys (eval key)))
192                        (return-from make-instance->constructor-call nil)))))
193       (check-class)
194       (check-args)
195       ;;
196       ;; Collect a plist of initargs and constant values/parameter names
197       ;; in INITARGS.  Collect non-constant initialization forms in
198       ;; VALUE-FORMS.
199       (multiple-value-bind (initargs value-forms)
200           (loop for (key value) on args by #'cddr and i from 0
201                 collect (eval key) into initargs
202                 if (constantp value)
203                   collect value into initargs
204                 else
205                   collect (parameter-name i) into initargs
206                   and collect value into value-forms
207                 finally
208                   (return (values initargs value-forms)))
209         (let* ((class-name (eval class-name))
210                (function-name (make-ctor-function-name class-name initargs)))
211           ;;
212           ;; Prevent compiler warnings for calling the ctor.
213           (sb-kernel:proclaim-as-fun-name function-name)
214           (sb-kernel:note-name-defined function-name :function)
215           (when (eq (info :function :where-from function-name) :assumed)
216             (setf (info :function :where-from function-name) :defined)
217             (when (info :function :assumed-type function-name)
218               (setf (info :function :assumed-type function-name) nil)))
219           ;;
220           ;; Return code constructing a ctor at load time, which, when
221           ;; called, will set its funcallable instance function to an
222           ;; optimized constructor function.
223           `(let ((.x. (load-time-value
224                        (ensure-ctor ',function-name ',class-name ',initargs))))
225              (declare (ignore .x.))
226              ;;; ??? check if this is worth it.
227              (declare
228               (ftype (or (function ,(make-list (length value-forms)
229                                                :initial-element t)
230                                    t)
231                          (function (&rest t) t))
232                      ,function-name))
233              (,function-name ,@value-forms)))))))
234
235 \f
236 ;;; **************************************************
237 ;;; Load-Time Constructor Function Generation  *******
238 ;;; **************************************************
239
240 ;;;
241 ;;; The system-supplied primary INITIALIZE-INSTANCE and
242 ;;; SHARED-INITIALIZE methods.  One cannot initialized these variables
243 ;;; to the right values here because said functions don't exist yet
244 ;;; when this file is first loaded.
245 ;;;
246 (defvar *the-system-ii-method* nil)
247 (defvar *the-system-si-method* nil)
248
249 (defun install-optimized-constructor (ctor)
250   (let ((class (find-class (ctor-class-name ctor))))
251     (unless (class-finalized-p class)
252       (finalize-inheritance class))
253     (setf (ctor-class ctor) class)
254     (pushnew ctor (plist-value class 'ctors))
255     (setf (sb-kernel:funcallable-instance-fun ctor)
256           ;; KLUDGE: Gerd here has the equivalent of (COMPILE NIL
257           ;; (CONSTRUCTOR-FUNCTION-FORM)), but SBCL's COMPILE doesn't
258           ;; deal with INSTANCE-LAMBDA expressions, only with LAMBDA
259           ;; expressions.  The below should be equivalent, since we
260           ;; have a compiler-only implementation.
261           (eval `(function ,(constructor-function-form ctor))))))
262               
263 (defun constructor-function-form (ctor)
264   (let* ((class (ctor-class ctor))
265          (proto (class-prototype class))
266          (make-instance-methods
267           (compute-applicable-methods #'make-instance (list class)))
268          (allocate-instance-methods
269           (compute-applicable-methods #'allocate-instance (list class)))
270          (ii-methods
271           (compute-applicable-methods #'initialize-instance (list proto)))
272          (si-methods
273           (compute-applicable-methods #'shared-initialize (list proto t))))
274     ;; Cannot initialize these variables earlier because the generic
275     ;; functions don't exist when PCL is built.
276     (when (null *the-system-si-method*)
277       (setq *the-system-si-method*
278             (find-method #'shared-initialize
279                          () (list *the-class-slot-object* *the-class-t*)))
280       (setq *the-system-ii-method*
281             (find-method #'initialize-instance
282                          () (list *the-class-slot-object*))))
283     ;; Note that when there are user-defined applicable methods on
284     ;; MAKE-INSTANCE and/or ALLOCATE-INSTANCE, these will show up
285     ;; together with the system-defined ones in what
286     ;; COMPUTE-APPLICABLE-METHODS returns.
287     (or (and (not (structure-class-p class))
288              (null (cdr make-instance-methods))
289              (null (cdr allocate-instance-methods))
290              (check-initargs-1 class (plist-keys (ctor-initargs ctor))
291                                (append ii-methods si-methods) nil nil)
292              (not (around-or-nonstandard-primary-method-p
293                    ii-methods *the-system-ii-method*))
294              (not (around-or-nonstandard-primary-method-p
295                    si-methods *the-system-si-method*))
296              (optimizing-generator ctor ii-methods si-methods))
297         (fallback-generator ctor ii-methods si-methods))))
298
299 (defun around-or-nonstandard-primary-method-p
300     (methods &optional standard-method)
301   (loop with primary-checked-p = nil
302         for method in methods
303         as qualifiers = (method-qualifiers method)
304         when (or (eq :around (car qualifiers))
305                  (and (null qualifiers)
306                       (not primary-checked-p)
307                       (not (null standard-method))
308                       (not (eq standard-method method))))
309           return t
310         when (null qualifiers) do
311           (setq primary-checked-p t)))
312
313 (defun fallback-generator (ctor ii-methods si-methods)
314   (declare (ignore ii-methods si-methods))
315   `(sb-kernel:instance-lambda ,(make-ctor-parameter-list ctor)
316      (make-instance ,(ctor-class ctor) ,@(ctor-initargs ctor))))
317
318 (defun optimizing-generator (ctor ii-methods si-methods)
319   (multiple-value-bind (body before-method-p)
320       (fake-initialization-emf ctor ii-methods si-methods)
321     `(sb-kernel:instance-lambda ,(make-ctor-parameter-list ctor)
322        (declare #.*optimize-speed*)
323        ,(wrap-in-allocate-forms ctor body before-method-p))))
324
325 ;;;
326 ;;; Return a form wrapped around BODY that allocates an instance
327 ;;; constructed by CTOR.  BEFORE-METHOD-P set means we have to run
328 ;;; before-methods, in which case we initialize instance slots to
329 ;;; +SLOT-UNBOUND+.  The resulting form binds the local variables
330 ;;; .INSTANCE. to the instance, and .SLOTS. to the instance's slot
331 ;;; vector around BODY.
332 ;;;
333 (defun wrap-in-allocate-forms (ctor body before-method-p)
334   (let* ((class (ctor-class ctor))
335          (wrapper (class-wrapper class))
336          (allocation-function (raw-instance-allocator class))
337          (slots-fetcher (slots-fetcher class)))
338     (if (eq allocation-function 'allocate-standard-instance)
339         `(let ((.instance. (%make-standard-instance nil
340                                                     (get-instance-hash-code)))
341                (.slots. (make-array
342                          ,(sb-kernel:layout-length wrapper)
343                          ,@(when before-method-p
344                              '(:initial-element +slot-unbound+)))))
345            (setf (std-instance-wrapper .instance.) ,wrapper)
346            (setf (std-instance-slots .instance.) .slots.)
347            ,body
348            .instance.)
349         `(let* ((.instance. (,allocation-function ,wrapper))
350                 (.slots. (,slots-fetcher .instance.)))
351            ,body
352            .instance.))))
353
354 ;;;
355 ;;; Return a form for invoking METHOD with arguments from ARGS.  As
356 ;;; can be seen in METHOD-FUNCTION-FROM-FAST-FUNCTION, method
357 ;;; functions look like (LAMBDA (ARGS NEXT-METHODS) ...).  We could
358 ;;; call fast method functions directly here, but benchmarks show that
359 ;;; there's no speed to gain, so lets avoid the hair here.
360 ;;;
361 (defmacro invoke-method (method args)
362   `(funcall ,(method-function method) ,args ()))
363
364 ;;;
365 ;;; Return a form that is sort of an effective method comprising all
366 ;;; calls to INITIALIZE-INSTANCE and SHARED-INITIALIZE that would
367 ;;; normally have taken place when calling MAKE-INSTANCE.
368 ;;;
369 (defun fake-initialization-emf (ctor ii-methods si-methods)
370   (multiple-value-bind (ii-around ii-before ii-primary ii-after)
371       (standard-sort-methods ii-methods)
372     (declare (ignore ii-primary))
373     (multiple-value-bind (si-around si-before si-primary si-after)
374         (standard-sort-methods si-methods)
375       (declare (ignore si-primary))
376       (assert (and (null ii-around) (null si-around)))
377       (let ((initargs (ctor-initargs ctor))
378             (slot-inits (slot-init-forms ctor (or ii-before si-before))))
379         (values
380          `(let (,@(when (or ii-before ii-after)
381                    `((.ii-args. (list .instance. ,@initargs))))
382                 ,@(when (or si-before si-after)
383                    `((.si-args. (list .instance. t ,@initargs)))))
384             ,@(loop for method in ii-before
385                     collect `(invoke-method ,method .ii-args.))
386             ,@(loop for method in si-before
387                     collect `(invoke-method ,method .si-args.))
388             ,slot-inits
389             ,@(loop for method in si-after
390                     collect `(invoke-method ,method .si-args.))
391             ,@(loop for method in ii-after
392                     collect `(invoke-method ,method .ii-args.)))
393          (or ii-before si-before))))))
394
395 ;;;
396 ;;; Return four values from APPLICABLE-METHODS: around methods, before
397 ;;; methods, the applicable primary method, and applicable after
398 ;;; methods.  Before and after methods are sorted in the order they
399 ;;; must be called.
400 ;;;
401 (defun standard-sort-methods (applicable-methods)
402   (loop for method in applicable-methods
403         as qualifiers = (method-qualifiers method)
404         if (null qualifiers)
405           collect method into primary
406         else if (eq :around (car qualifiers))
407           collect method into around
408         else if (eq :after (car qualifiers))
409           collect method into after
410         else if (eq :before (car qualifiers))
411           collect method into before
412         finally
413           (return (values around before (first primary) (reverse after)))))
414
415 ;;;
416 ;;; Return a form initializing instance and class slots of an object
417 ;;; costructed by CTOR.  The variable .SLOTS. is assumed to bound to
418 ;;; the instance's slot vector.  BEFORE-METHOD-P T means
419 ;;; before-methods will be called, which means that 1) other code will
420 ;;; initialize instance slots to +SLOT-UNBOUND+ before the
421 ;;; before-methods are run, and that we have to check if these
422 ;;; before-methods have set slots.
423 ;;;
424 (defun slot-init-forms (ctor before-method-p)
425   (let* ((class (ctor-class ctor))
426          (initargs (ctor-initargs ctor))
427          (initkeys (plist-keys initargs))
428          (slot-vector
429           (make-array (sb-kernel:layout-length (class-wrapper class))
430                       :initial-element nil))
431          (class-inits ())
432          (default-initargs (class-default-initargs class))
433          (initarg-locations
434           (compute-initarg-locations
435            class (append initkeys (mapcar #'car default-initargs)))))
436     (labels ((initarg-locations (initarg)
437                (cdr (assoc initarg initarg-locations :test #'eq)))
438
439              (class-init (location type val)
440                (assert (consp location))
441                (unless (assoc location class-inits :test #'eq)
442                  (push (list location type val) class-inits)))
443
444              (instance-init (location type val)
445                (assert (integerp location))
446                (assert (not (instance-slot-initialized-p location)))
447                (setf (aref slot-vector location) (list type val)))
448
449              (instance-slot-initialized-p (location)
450                (not (null (aref slot-vector location)))))
451       ;;
452       ;; Loop over supplied initargs and values and record which
453       ;; instance and class slots they initialize.
454       (loop for (key value) on initargs by #'cddr
455             as locations = (initarg-locations key) do
456               (if (constantp value)
457                   (dolist (location locations)
458                     (if (consp location)
459                         (class-init location 'constant value)
460                         (instance-init location 'constant value)))
461                     (dolist (location locations)
462                       (if (consp location)
463                           (class-init location 'param value)
464                           (instance-init location 'param value)))))
465       ;;
466       ;; Loop over default initargs of the class, recording
467       ;; initializations of slots that have not been initialized
468       ;; above.
469       (loop for (key initfn initform) in default-initargs do
470               (unless (member key initkeys :test #'eq)
471                 (if (constantp initform)
472                     (dolist (location (initarg-locations key))
473                       (if (consp location)
474                           (class-init location 'constant initform)
475                           (instance-init location 'constant initform)))
476                     (dolist (location (initarg-locations key))
477                       (if (consp location)
478                           (class-init location 'initfn initfn)
479                           (instance-init location 'initfn initfn))))))
480       ;;
481       ;; Loop over all slots of the class, filling in the rest from
482       ;; slot initforms.
483       (loop for slotd in (class-slots class)
484             as location = (slot-definition-location slotd)
485             as allocation = (slot-definition-allocation slotd)
486             as initfn = (slot-definition-initfunction slotd)
487             as initform = (slot-definition-initform slotd) do
488               (unless (or (eq allocation :class)
489                           (null initfn)
490                           (instance-slot-initialized-p location))
491                 (if (constantp initform)
492                     (instance-init location 'initform initform)
493                     (instance-init location 'initform/initfn initfn))))
494       ;;
495       ;; Generate the forms for initializing instance and class slots.
496       (let ((instance-init-forms
497              (loop for slot-entry across slot-vector and i from 0
498                    as (type value) = slot-entry collect
499                      (ecase type
500                        ((nil)
501                         (unless before-method-p
502                           `(setf (clos-slots-ref .slots. ,i) +slot-unbound+)))
503                        (param
504                         `(setf (clos-slots-ref .slots. ,i) ,value))
505                        (initfn
506                         `(setf (clos-slots-ref .slots. ,i) (funcall ,value)))
507                        (initform/initfn
508                         (if before-method-p
509                             `(when (eq (clos-slots-ref .slots. ,i)
510                                        +slot-unbound+)
511                                (setf (clos-slots-ref .slots. ,i)
512                                      (funcall ,value)))
513                             `(setf (clos-slots-ref .slots. ,i)
514                                    (funcall ,value))))
515                        (initform
516                         (if before-method-p
517                             `(when (eq (clos-slots-ref .slots. ,i)
518                                        +slot-unbound+)
519                                (setf (clos-slots-ref .slots. ,i)
520                                      ',(eval value)))
521                             `(setf (clos-slots-ref .slots. ,i)
522                                    ',(eval value))))
523                        (constant
524                         `(setf (clos-slots-ref .slots. ,i) ',(eval value))))))
525             (class-init-forms
526              (loop for (location type value) in class-inits collect
527                      `(setf (cdr ',location)
528                             ,(ecase type
529                                     (constant `',(eval value))
530                                     (param `,value)
531                                     (initfn `(funcall ,value)))))))
532         `(progn
533            ,@(delete nil instance-init-forms)
534            ,@class-init-forms)))))
535
536 ;;;
537 ;;; Return an alist of lists (KEY LOCATION ...) telling, for each
538 ;;; key in INITKEYS, which locations the initarg initializes.
539 ;;; CLASS is the class of the instance being initialized.
540 ;;;
541 (defun compute-initarg-locations (class initkeys)
542   (loop with slots = (class-slots class)
543         for key in initkeys collect
544           (loop for slot in slots
545                 if (memq key (slot-definition-initargs slot))
546                   collect (slot-definition-location slot) into locations
547                 else
548                   collect slot into remaining-slots
549                 finally
550                   (setq slots remaining-slots)
551                   (return (cons key locations)))))
552
553 \f
554 ;;; *******************************
555 ;;; External Entry Points  ********
556 ;;; *******************************
557
558 (defun update-ctors (reason &key class name generic-function method)
559   (flet ((reset-class-ctors (class)
560            (loop for ctor in (plist-value class 'ctors) do
561                    (install-initial-constructor ctor))))
562     (ecase reason
563       ;;
564       ;; CLASS must have been specified.
565       (finalize-inheritance
566        (reset-class-ctors class))
567       ;;
568       ;; NAME must have been specified.
569       (setf-find-class
570        (loop for ctor in *all-ctors*
571              when (eq (ctor-class-name ctor) name) do
572              (when (ctor-class ctor)
573                (reset-class-ctors (ctor-class ctor)))
574              (loop-finish)))
575       ;;
576       ;; GENERIC-FUNCTION and METHOD must have been specified.
577       ((add-method remove-method)
578        (case (generic-function-name generic-function)
579          ((make-instance allocate-instance initialize-instance
580                          shared-initialize)
581           (let ((type (first (method-specializers method))))
582             (reset-class-ctors (type-class type)))))))))
583
584 (defun precompile-ctors ()
585   (dolist (ctor *all-ctors*)
586     (when (null (ctor-class ctor))
587       (let ((class (find-class (ctor-class-name ctor) nil)))
588         (when (and class (class-finalized-p class))
589           (install-optimized-constructor ctor))))))
590
591 ;;; end of ctor.lisp