0.8.15:
[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 quote-plist-keys (plist)
66   (loop for (key . more) on plist by #'cddr
67         if (null more) do
68           (error "Not a property list: ~S" plist)
69         else
70           collect `(quote ,key)
71           and collect (car more)))
72
73 (defun plist-keys (plist &key test)
74   (loop for (key . more) on plist by #'cddr
75         if (null more) do
76           (error "Not a property list: ~S" plist)
77         else if (or (null test) (funcall test key))
78           collect key))
79
80 (defun plist-values (plist &key test)
81   (loop for (key . more) on plist by #'cddr
82         if (null more) do
83           (error "Not a property list: ~S" plist)
84         else if (or (null test) (funcall test (car more)))
85           collect (car more)))
86
87 (defun constant-symbol-p (form)
88   (and (constantp form)
89        (let ((constant (eval form)))
90          (and (symbolp constant)
91               (not (null (symbol-package constant)))))))
92
93 \f
94 ;;; *****************
95 ;;; CTORS   *********
96 ;;; *****************
97 ;;;
98 ;;; Ctors are funcallable instances whose initial function is a
99 ;;; function computing an optimized constructor function when called.
100 ;;; When the optimized function is computed, the function of the
101 ;;; funcallable instance is set to it.
102 ;;;
103 (!defstruct-with-alternate-metaclass ctor
104   :slot-names (function-name class-name class initargs)
105   :boa-constructor %make-ctor
106   :superclass-name pcl-funcallable-instance
107   :metaclass-name random-pcl-classoid
108   :metaclass-constructor make-random-pcl-classoid
109   :dd-type funcallable-structure
110   :runtime-type-checks-p nil)
111
112 ;;; List of all defined ctors.
113
114 (defvar *all-ctors* ())
115
116 (defun make-ctor-parameter-list (ctor)
117   (plist-values (ctor-initargs ctor) :test (complement #'constantp)))
118
119 ;;; Reset CTOR to use a default function that will compute an
120 ;;; optimized constructor function when called.
121 (defun install-initial-constructor (ctor &key force-p)
122   (when (or force-p (ctor-class ctor))
123     (setf (ctor-class ctor) nil)
124     (setf (funcallable-instance-fun ctor)
125           #'(instance-lambda (&rest args)
126               (install-optimized-constructor ctor)
127               (apply ctor args)))
128     (setf (%funcallable-instance-info ctor 1)
129           (ctor-function-name ctor))))
130
131 ;;; Keep this a separate function for testing.
132 (defun make-ctor-function-name (class-name initargs)
133   (let ((*package* *pcl-package*)
134         (*print-case* :upcase)
135         (*print-pretty* nil)
136         (*print-gensym* t))
137     (format-symbol *pcl-package* "CTOR ~S::~S ~S ~S"
138                    (package-name (symbol-package class-name))
139                    (symbol-name class-name)
140                    (plist-keys initargs)
141                    (plist-values initargs :test #'constantp))))
142
143 ;;; Keep this a separate function for testing.
144 (defun ensure-ctor (function-name class-name initargs)
145   (unless (fboundp function-name)
146     (make-ctor function-name class-name initargs)))
147
148 ;;; Keep this a separate function for testing.
149 (defun make-ctor (function-name class-name initargs)
150   (without-package-locks ; for (setf symbol-function)
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                    (format-symbol *pcl-package* ".P~D." i))))
178            ;; Check if CLASS-NAME is a constant symbol.  Give up if
179            ;; not.
180            (check-class ()
181              (unless (and class-name (constant-symbol-p class-name))
182                (return-from make-instance->constructor-call nil)))
183            ;; Check if ARGS are suitable for an optimized constructor.
184            ;; Return NIL from the outer function if not.
185            (check-args ()
186              (loop for (key . more) on args by #'cddr do
187                      (when (or (null more)
188                                (not (constant-symbol-p key))
189                                (eq :allow-other-keys (eval key)))
190                        (return-from make-instance->constructor-call nil)))))
191       (check-class)
192       (check-args)
193       ;; Collect a plist of initargs and constant values/parameter names
194       ;; in INITARGS.  Collect non-constant initialization forms in
195       ;; VALUE-FORMS.
196       (multiple-value-bind (initargs value-forms)
197           (loop for (key value) on args by #'cddr and i from 0
198                 collect (eval key) into initargs
199                 if (constantp value)
200                   collect value into initargs
201                 else
202                   collect (parameter-name i) into initargs
203                   and collect value into value-forms
204                 finally
205                   (return (values initargs value-forms)))
206         (let* ((class-name (eval class-name))
207                (function-name (make-ctor-function-name class-name initargs)))
208           ;; Prevent compiler warnings for calling the ctor.
209           (proclaim-as-fun-name function-name)
210           (note-name-defined function-name :function)
211           (when (eq (info :function :where-from function-name) :assumed)
212             (setf (info :function :where-from function-name) :defined)
213             (when (info :function :assumed-type function-name)
214               (setf (info :function :assumed-type function-name) nil)))
215           ;; Return code constructing a ctor at load time, which, when
216           ;; called, will set its funcallable instance function to an
217           ;; optimized constructor function.
218           `(locally 
219                (declare (disable-package-locks ,function-name))
220             (let ((.x. (load-time-value
221                         (ensure-ctor ',function-name ',class-name ',initargs))))
222               (declare (ignore .x.))
223               ;; ??? check if this is worth it.
224               (declare
225                (ftype (or (function ,(make-list (length value-forms)
226                                                 :initial-element t)
227                                     t)
228                           (function (&rest t) t))
229                       ,function-name))
230               (,function-name ,@value-forms))))))))
231
232 \f
233 ;;; **************************************************
234 ;;; Load-Time Constructor Function Generation  *******
235 ;;; **************************************************
236
237 ;;; The system-supplied primary INITIALIZE-INSTANCE and
238 ;;; SHARED-INITIALIZE methods.  One cannot initialize these variables
239 ;;; to the right values here because said functions don't exist yet
240 ;;; when this file is first loaded.
241 (defvar *the-system-ii-method* nil)
242 (defvar *the-system-si-method* nil)
243
244 (defun install-optimized-constructor (ctor)
245   (let ((class (find-class (ctor-class-name ctor))))
246     (unless (class-finalized-p class)
247       (finalize-inheritance class))
248     (setf (ctor-class ctor) class)
249     (pushnew ctor (plist-value class 'ctors))
250     (setf (funcallable-instance-fun ctor)
251           ;; KLUDGE: Gerd here has the equivalent of (COMPILE NIL
252           ;; (CONSTRUCTOR-FUNCTION-FORM)), but SBCL's COMPILE doesn't
253           ;; deal with INSTANCE-LAMBDA expressions, only with LAMBDA
254           ;; expressions.  The below should be equivalent, since we
255           ;; have a compiler-only implementation.
256           ;;
257           ;; (except maybe for optimization qualities? -- CSR,
258           ;; 2004-07-12)
259           (eval `(function ,(constructor-function-form ctor))))))
260               
261 (defun constructor-function-form (ctor)
262   (let* ((class (ctor-class ctor))
263          (proto (class-prototype class))
264          (make-instance-methods
265           (compute-applicable-methods #'make-instance (list class)))
266          (allocate-instance-methods
267           (compute-applicable-methods #'allocate-instance (list class)))
268          ;; I stared at this in confusion for a while, thinking
269          ;; carefully about the possibility of the class prototype not
270          ;; being of sufficient discrimiating power, given the
271          ;; possibility of EQL-specialized methods on
272          ;; INITIALIZE-INSTANCE or SHARED-INITIALIZE.  However, given
273          ;; that this is a constructor optimization, the user doesn't
274          ;; yet have the instance to create a method with such an EQL
275          ;; specializer.
276          ;;
277          ;; There remains the (theoretical) possibility of someone
278          ;; coming along with code of the form
279          ;;
280          ;; (defmethod initialize-instance :before ((o foo) ...)
281          ;;   (eval `(defmethod shared-initialize :before ((o foo) ...) ...)))
282          ;;
283          ;; but probably we can afford not to worry about this too
284          ;; much for now.  -- CSR, 2004-07-12
285          (ii-methods
286           (compute-applicable-methods #'initialize-instance (list proto)))
287          (si-methods
288           (compute-applicable-methods #'shared-initialize (list proto t)))
289          (setf-svuc-slots-methods
290           (loop for slot in (class-slots class)
291                 collect (compute-applicable-methods
292                          #'(setf slot-value-using-class)
293                          (list nil class proto slot))))
294          (sbuc-slots-methods
295           (loop for slot in (class-slots class)
296                 collect (compute-applicable-methods
297                          #'slot-boundp-using-class
298                          (list class proto slot)))))
299     ;; Cannot initialize these variables earlier because the generic
300     ;; functions don't exist when PCL is built.
301     (when (null *the-system-si-method*)
302       (setq *the-system-si-method*
303             (find-method #'shared-initialize
304                          () (list *the-class-slot-object* *the-class-t*)))
305       (setq *the-system-ii-method*
306             (find-method #'initialize-instance
307                          () (list *the-class-slot-object*))))
308     ;; Note that when there are user-defined applicable methods on
309     ;; MAKE-INSTANCE and/or ALLOCATE-INSTANCE, these will show up
310     ;; together with the system-defined ones in what
311     ;; COMPUTE-APPLICABLE-METHODS returns.
312     (or (and (not (structure-class-p class))
313              (not (condition-class-p class))
314              (null (cdr make-instance-methods))
315              (null (cdr allocate-instance-methods))
316              (every (lambda (x)
317                       (member (slot-definition-allocation x)
318                               '(:instance :class)))
319                     (class-slots class))
320              (null (check-initargs-1 class (plist-keys (ctor-initargs ctor))
321                                      (append ii-methods si-methods) nil nil))
322              (not (around-or-nonstandard-primary-method-p
323                    ii-methods *the-system-ii-method*))
324              (not (around-or-nonstandard-primary-method-p
325                    si-methods *the-system-si-method*))
326              ;; the instance structure protocol goes through
327              ;; slot-value(-using-class) and friends (actually just
328              ;; (SETF SLOT-VALUE-USING-CLASS) and
329              ;; SLOT-BOUNDP-USING-CLASS), so if there are non-standard
330              ;; applicable methods we can't shortcircuit them.
331              (every (lambda (x) (= (length x) 1)) setf-svuc-slots-methods)
332              (every (lambda (x) (= (length x) 1)) sbuc-slots-methods)
333              (optimizing-generator ctor ii-methods si-methods))
334         (fallback-generator ctor ii-methods si-methods))))
335
336 (defun around-or-nonstandard-primary-method-p
337     (methods &optional standard-method)
338   (loop with primary-checked-p = nil
339         for method in methods
340         as qualifiers = (method-qualifiers method)
341         when (or (eq :around (car qualifiers))
342                  (and (null qualifiers)
343                       (not primary-checked-p)
344                       (not (null standard-method))
345                       (not (eq standard-method method))))
346           return t
347         when (null qualifiers) do
348           (setq primary-checked-p t)))
349
350 (defun fallback-generator (ctor ii-methods si-methods)
351   (declare (ignore ii-methods si-methods))
352   `(instance-lambda ,(make-ctor-parameter-list ctor)
353      ;; The CTOR MAKE-INSTANCE optimization only kicks in when the
354      ;; first argument to MAKE-INSTANCE is a constant symbol: by
355      ;; calling it with a class, as here, we inhibit the optimization,
356      ;; so removing the possibility of endless recursion.  -- CSR,
357      ;; 2004-07-12
358      (make-instance ,(ctor-class ctor) ,@(ctor-initargs ctor))))
359
360 (defun optimizing-generator (ctor ii-methods si-methods)
361   (multiple-value-bind (body before-method-p)
362       (fake-initialization-emf ctor ii-methods si-methods)
363     `(instance-lambda ,(make-ctor-parameter-list ctor)
364        (declare #.*optimize-speed*)
365        ,(wrap-in-allocate-forms ctor body before-method-p))))
366
367 ;;; Return a form wrapped around BODY that allocates an instance
368 ;;; constructed by CTOR.  BEFORE-METHOD-P set means we have to run
369 ;;; before-methods, in which case we initialize instance slots to
370 ;;; +SLOT-UNBOUND+.  The resulting form binds the local variables
371 ;;; .INSTANCE. to the instance, and .SLOTS. to the instance's slot
372 ;;; vector around BODY.
373 (defun wrap-in-allocate-forms (ctor body before-method-p)
374   (let* ((class (ctor-class ctor))
375          (wrapper (class-wrapper class))
376          (allocation-function (raw-instance-allocator class))
377          (slots-fetcher (slots-fetcher class)))
378     (if (eq allocation-function 'allocate-standard-instance)
379         `(let ((.instance. (%make-standard-instance nil
380                                                     (get-instance-hash-code)))
381                (.slots. (make-array
382                          ,(layout-length wrapper)
383                          ,@(when before-method-p
384                              '(:initial-element +slot-unbound+)))))
385            (setf (std-instance-wrapper .instance.) ,wrapper)
386            (setf (std-instance-slots .instance.) .slots.)
387            ,body
388            .instance.)
389         `(let* ((.instance. (,allocation-function ,wrapper))
390                 (.slots. (,slots-fetcher .instance.)))
391            ,body
392            .instance.))))
393
394 ;;; Return a form for invoking METHOD with arguments from ARGS.  As
395 ;;; can be seen in METHOD-FUNCTION-FROM-FAST-FUNCTION, method
396 ;;; functions look like (LAMBDA (ARGS NEXT-METHODS) ...).  We could
397 ;;; call fast method functions directly here, but benchmarks show that
398 ;;; there's no speed to gain, so lets avoid the hair here.
399 (defmacro invoke-method (method args)
400   `(funcall ,(method-function method) ,args ()))
401
402 ;;; Return a form that is sort of an effective method comprising all
403 ;;; calls to INITIALIZE-INSTANCE and SHARED-INITIALIZE that would
404 ;;; normally have taken place when calling MAKE-INSTANCE.
405 (defun fake-initialization-emf (ctor ii-methods si-methods)
406   (multiple-value-bind (ii-around ii-before ii-primary ii-after)
407       (standard-sort-methods ii-methods)
408     (declare (ignore ii-primary))
409     (multiple-value-bind (si-around si-before si-primary si-after)
410         (standard-sort-methods si-methods)
411       (declare (ignore si-primary))
412       (aver (and (null ii-around) (null si-around)))
413       (let ((initargs (ctor-initargs ctor))
414             (slot-inits (slot-init-forms ctor (or ii-before si-before))))
415         (values
416          `(let (,@(when (or ii-before ii-after)
417                    `((.ii-args.
418                       (list .instance. ,@(quote-plist-keys initargs)))))
419                 ,@(when (or si-before si-after)
420                    `((.si-args.
421                       (list .instance. t ,@(quote-plist-keys initargs))))))
422             ,@(loop for method in ii-before
423                     collect `(invoke-method ,method .ii-args.))
424             ,@(loop for method in si-before
425                     collect `(invoke-method ,method .si-args.))
426             ,slot-inits
427             ,@(loop for method in si-after
428                     collect `(invoke-method ,method .si-args.))
429             ,@(loop for method in ii-after
430                     collect `(invoke-method ,method .ii-args.)))
431          (or ii-before si-before))))))
432
433 ;;; Return four values from APPLICABLE-METHODS: around methods, before
434 ;;; methods, the applicable primary method, and applicable after
435 ;;; methods.  Before and after methods are sorted in the order they
436 ;;; must be called.
437 (defun standard-sort-methods (applicable-methods)
438   (loop for method in applicable-methods
439         as qualifiers = (method-qualifiers method)
440         if (null qualifiers)
441           collect method into primary
442         else if (eq :around (car qualifiers))
443           collect method into around
444         else if (eq :after (car qualifiers))
445           collect method into after
446         else if (eq :before (car qualifiers))
447           collect method into before
448         finally
449           (return (values around before (first primary) (reverse after)))))
450
451 ;;; Return a form initializing instance and class slots of an object
452 ;;; costructed by CTOR.  The variable .SLOTS. is assumed to bound to
453 ;;; the instance's slot vector.  BEFORE-METHOD-P T means
454 ;;; before-methods will be called, which means that 1) other code will
455 ;;; initialize instance slots to +SLOT-UNBOUND+ before the
456 ;;; before-methods are run, and that we have to check if these
457 ;;; before-methods have set slots.
458 (defun slot-init-forms (ctor before-method-p)
459   (let* ((class (ctor-class ctor))
460          (initargs (ctor-initargs ctor))
461          (initkeys (plist-keys initargs))
462          (slot-vector
463           (make-array (layout-length (class-wrapper class))
464                       :initial-element nil))
465          (class-inits ())
466          (default-inits ())
467          (default-initargs (class-default-initargs class))
468          (initarg-locations
469           (compute-initarg-locations
470            class (append initkeys (mapcar #'car default-initargs)))))
471     (labels ((initarg-locations (initarg)
472                (cdr (assoc initarg initarg-locations :test #'eq)))
473              (initializedp (location)
474                (cond
475                  ((consp location)
476                   (assoc location class-inits :test #'eq))
477                  ((integerp location)
478                   (not (null (aref slot-vector location))))
479                  (t (bug "Weird location in ~S" 'slot-init-forms))))
480              (class-init (location type val)
481                (aver (consp location))
482                (unless (initializedp location)
483                  (push (list location type val) class-inits)))
484              (instance-init (location type val)
485                (aver (integerp location))
486                (unless (initializedp location)
487                  (setf (aref slot-vector location) (list type val))))
488              (default-init-var-name (i)
489                (let ((ps #(.d0. .d1. .d2. .d3. .d4. .d5.)))
490                  (if (array-in-bounds-p ps i)
491                      (aref ps i)
492                      (format-symbol *pcl-package* ".D~D." i)))))
493       ;; Loop over supplied initargs and values and record which
494       ;; instance and class slots they initialize.
495       (loop for (key value) on initargs by #'cddr
496             as locations = (initarg-locations key) do
497               (if (constantp value)
498                   (dolist (location locations)
499                     (if (consp location)
500                         (class-init location 'constant value)
501                         (instance-init location 'constant value)))
502                   (dolist (location locations)
503                       (if (consp location)
504                           (class-init location 'param value)
505                           (instance-init location 'param value)))))
506       ;; Loop over default initargs of the class, recording
507       ;; initializations of slots that have not been initialized
508       ;; above.  Default initargs which are not in the supplied
509       ;; initargs are treated as if they were appended to supplied
510       ;; initargs, that is, their values must be evaluated even
511       ;; if not actually used for initializing a slot.
512       (loop for (key initfn initform) in default-initargs and i from 0
513             unless (member key initkeys :test #'eq) do
514             (let* ((type (if (constantp initform) 'constant 'var))
515                    (init (if (eq type 'var) initfn initform)))
516               (when (eq type 'var)
517                 (let ((init-var (default-init-var-name i)))
518                   (setq init init-var)
519                   (push (cons init-var initfn) default-inits)))
520               (dolist (location (initarg-locations key))
521                 (if (consp location)
522                     (class-init location type init)
523                     (instance-init location type init)))))
524       ;; Loop over all slots of the class, filling in the rest from
525       ;; slot initforms.
526       (loop for slotd in (class-slots class)
527             as location = (slot-definition-location slotd)
528             as allocation = (slot-definition-allocation slotd)
529             as initfn = (slot-definition-initfunction slotd)
530             as initform = (slot-definition-initform slotd) do
531               (unless (or (eq allocation :class)
532                           (null initfn)
533                           (initializedp location))
534                 (if (constantp initform)
535                     (instance-init location 'initform initform)
536                     (instance-init location 'initform/initfn initfn))))
537       ;; Generate the forms for initializing instance and class slots.
538       (let ((instance-init-forms
539              (loop for slot-entry across slot-vector and i from 0
540                    as (type value) = slot-entry collect
541                      (ecase type
542                        ((nil)
543                         (unless before-method-p
544                           `(setf (clos-slots-ref .slots. ,i) +slot-unbound+)))
545                        ((param var)
546                         `(setf (clos-slots-ref .slots. ,i) ,value))
547                        (initfn
548                         `(setf (clos-slots-ref .slots. ,i) (funcall ,value)))
549                        (initform/initfn
550                         (if before-method-p
551                             `(when (eq (clos-slots-ref .slots. ,i)
552                                        +slot-unbound+)
553                                (setf (clos-slots-ref .slots. ,i)
554                                      (funcall ,value)))
555                             `(setf (clos-slots-ref .slots. ,i)
556                                    (funcall ,value))))
557                        (initform
558                         (if before-method-p
559                             `(when (eq (clos-slots-ref .slots. ,i)
560                                        +slot-unbound+)
561                                (setf (clos-slots-ref .slots. ,i)
562                                      ',(eval value)))
563                             `(setf (clos-slots-ref .slots. ,i)
564                                    ',(eval value))))
565                        (constant
566                         `(setf (clos-slots-ref .slots. ,i) ',(eval value))))))
567             (class-init-forms
568              (loop for (location type value) in class-inits collect
569                      `(setf (cdr ',location)
570                             ,(ecase type
571                                (constant `',(eval value))
572                                ((param var) `,value)
573                                (initfn `(funcall ,value)))))))
574         (multiple-value-bind (vars bindings)
575             (loop for (var . initfn) in (nreverse default-inits)
576                   collect var into vars
577                   collect `(,var (funcall ,initfn)) into bindings
578                   finally (return (values vars bindings)))
579           `(let ,bindings
580              (declare (ignorable ,@vars))
581              ,@(delete nil instance-init-forms)
582              ,@class-init-forms))))))
583
584 ;;; Return an alist of lists (KEY LOCATION ...) telling, for each
585 ;;; key in INITKEYS, which locations the initarg initializes.
586 ;;; CLASS is the class of the instance being initialized.
587 (defun compute-initarg-locations (class initkeys)
588   (loop with slots = (class-slots class)
589         for key in initkeys collect
590           (loop for slot in slots
591                 if (memq key (slot-definition-initargs slot))
592                   collect (slot-definition-location slot) into locations
593                 else
594                   collect slot into remaining-slots
595                 finally
596                   (setq slots remaining-slots)
597                   (return (cons key locations)))))
598
599 \f
600 ;;; *******************************
601 ;;; External Entry Points  ********
602 ;;; *******************************
603
604 (defun update-ctors (reason &key class name generic-function method)
605   (labels ((reset (class &optional ri-cache-p (ctorsp t))
606              (when ctorsp
607                (dolist (ctor (plist-value class 'ctors))
608                  (install-initial-constructor ctor)))
609              (when ri-cache-p
610                (setf (plist-value class 'ri-initargs) ()))
611              (dolist (subclass (class-direct-subclasses class))
612                (reset subclass ri-cache-p ctorsp))))
613     (ecase reason
614       ;; CLASS must have been specified.
615       (finalize-inheritance
616        (reset class t))
617       ;; NAME must have been specified.
618       (setf-find-class
619        (loop for ctor in *all-ctors*
620              when (eq (ctor-class-name ctor) name) do
621              (when (ctor-class ctor)
622                (reset (ctor-class ctor)))
623              (loop-finish)))
624       ;; GENERIC-FUNCTION and METHOD must have been specified.
625       ((add-method remove-method)
626        (flet ((class-of-1st-method-param (method)
627                 (type-class (first (method-specializers method)))))
628          (case (generic-function-name generic-function)
629            ((make-instance allocate-instance
630              initialize-instance shared-initialize)
631             (reset (class-of-1st-method-param method) t t))
632            ((reinitialize-instance)
633             (reset (class-of-1st-method-param method) t nil))
634            (t (when (or (eq (generic-function-name generic-function)
635                             'slot-boundp-using-class)
636                         (equal (generic-function-name generic-function)
637                                '(setf slot-value-using-class)))
638                 ;; this looks awfully expensive, but given that one
639                 ;; can specialize on the SLOTD argument, nothing is
640                 ;; safe.  -- CSR, 2004-07-12
641                 (reset (find-class 'standard-object))))))))))
642
643 (defun precompile-ctors ()
644   (dolist (ctor *all-ctors*)
645     (when (null (ctor-class ctor))
646       (let ((class (find-class (ctor-class-name ctor) nil)))
647         (when (and class (class-finalized-p class))
648           (install-optimized-constructor ctor))))))
649
650 (defun check-ri-initargs (instance initargs)
651   (let* ((class (class-of instance))
652          (keys (plist-keys initargs))
653          (cached (assoc keys (plist-value class 'ri-initargs)
654                         :test #'equal))
655          (invalid-keys
656           (if (consp cached)
657               (cdr cached)
658               (let ((invalid
659                      ;; FIXME: give CHECK-INITARGS-1 and friends a
660                      ;; more mnemonic name and (possibly) a nicer,
661                      ;; more orthogonal interface.
662                      (check-initargs-1
663                       class initargs
664                       (list (list* 'reinitialize-instance instance initargs)
665                             (list* 'shared-initialize instance nil initargs))
666                       t nil)))
667                 (setf (plist-value class 'ri-initargs)
668                       (acons keys invalid cached))
669                 invalid))))
670     (when invalid-keys
671       (error 'initarg-error :class class :initargs invalid-keys))))
672
673 ;;; end of ctor.lisp