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