1.0.29.41: inline CTOR caches for MAKE-INSTANCE
[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-class-arg-p (form)
88   (and (constantp form)
89        (let ((constant (constant-form-value form)))
90          (or (and (symbolp constant)
91                   (not (null (symbol-package constant))))
92              (classp form)))))
93
94 (defun constant-symbol-p (form)
95   (and (constantp form)
96        (let ((constant (constant-form-value form)))
97          (and (symbolp constant)
98               (not (null (symbol-package constant)))))))
99
100 ;;; somewhat akin to DEFAULT-INITARGS (SLOT-CLASS T T), but just
101 ;;; collecting the defaulted initargs for the call.
102 (defun ctor-default-initkeys (supplied-initargs class-default-initargs)
103   (loop for (key) in class-default-initargs
104         when (eq (getf supplied-initargs key '.not-there.) '.not-there.)
105         collect key))
106 \f
107 ;;; *****************
108 ;;; CTORS   *********
109 ;;; *****************
110 ;;;
111 ;;; Ctors are funcallable instances whose initial function is a
112 ;;; function computing an optimized constructor function when called.
113 ;;; When the optimized function is computed, the function of the
114 ;;; funcallable instance is set to it.
115 ;;;
116 (!defstruct-with-alternate-metaclass ctor
117   :slot-names (function-name class-or-name class initargs safe-p)
118   :boa-constructor %make-ctor
119   :superclass-name function
120   :metaclass-name static-classoid
121   :metaclass-constructor make-static-classoid
122   :dd-type funcallable-structure
123   :runtime-type-checks-p nil)
124
125 ;;; List of all defined ctors.
126 (defvar *all-ctors* ())
127
128 (defun make-ctor-parameter-list (ctor)
129   (plist-values (ctor-initargs ctor) :test (complement #'constantp)))
130
131 ;;; Reset CTOR to use a default function that will compute an
132 ;;; optimized constructor function when called.
133 (defun install-initial-constructor (ctor &key force-p)
134   (when (or force-p (ctor-class ctor))
135     (let ((*installing-ctor* t))
136       (setf (ctor-class ctor) nil)
137       (setf (funcallable-instance-fun ctor)
138             #'(lambda (&rest args)
139                 (install-optimized-constructor ctor)
140                 (apply ctor args)))
141       (setf (%funcallable-instance-info ctor 1)
142             (ctor-function-name ctor)))))
143
144 (defun make-ctor-function-name (class-name initargs safe-code-p)
145   (list* 'ctor class-name safe-code-p initargs))
146
147 ;;; Keep this a separate function for testing.
148 (defun ensure-ctor (function-name class-name initargs safe-code-p)
149   (unless (fboundp function-name)
150     (make-ctor function-name class-name initargs safe-code-p)))
151
152 ;;; Keep this a separate function for testing.
153 (defun make-ctor (function-name class-name initargs safe-p)
154   (without-package-locks ; for (setf symbol-function)
155    (let ((ctor (%make-ctor function-name class-name nil initargs safe-p)))
156      (push ctor *all-ctors*)
157      (setf (fdefinition function-name) ctor)
158      (install-initial-constructor ctor :force-p t)
159      ctor)))
160 \f
161 ;;; *****************
162 ;;; Inline CTOR cache
163 ;;; *****************
164 ;;;
165 ;;; The cache starts out as a list of CTORs, sorted with the most recently
166 ;;; used CTORs near the head. If it expands too much, we switch to a vector
167 ;;; with a simple hashing scheme.
168
169 ;;; Find CTOR for KEY (which is a class or class name) in a list. If the CTOR
170 ;;; is in the list but not one of the 4 first ones, return a new list with the
171 ;;; found CTOR at the head. Thread-safe: the new list shares structure with
172 ;;; the old, but is not desctructively modified. Returning the old list for
173 ;;; hits close to the head reduces ping-ponging with multiple threads seeking
174 ;;; the same list.
175 (defun find-ctor (key list)
176   (labels ((walk (tail from-head depth)
177              (declare (fixnum depth))
178              (if tail
179                  (let ((ctor (car tail)))
180                    (if (eq (ctor-class-or-name ctor) key)
181                        (if (> depth 3)
182                            (values ctor
183                                    (nconc (list ctor) (nreverse from-head) (cdr tail)))
184                            (values ctor
185                                    list))
186                        (walk (cdr tail)
187                              (cons ctor from-head)
188                              (logand #xf (1+ depth)))))
189                  (values nil list))))
190     (walk list nil 0)))
191
192 (declaim (inline sxhash-symbol-or-class))
193 (defun sxhash-symbol-or-class (x)
194   (cond ((symbolp x) (sxhash x))
195         ((std-instance-p x) (std-instance-hash x))
196         ((fsc-instance-p x) (fsc-instance-hash x))
197         (t
198          (bug "Something strange where symbol or class expected."))))
199
200 ;;; Max number of CTORs kept in an inline list cache. Once this is
201 ;;; exceeded we switch to a table.
202 (defconstant +ctor-list-max-size+ 12)
203 ;;; Max table size for CTOR cache. If the table fills up at this size
204 ;;; we keep the same size and drop 50% of the old entries.
205 (defconstant +ctor-table-max-size+ (expt 2 8))
206 ;;; Even if there is space in the cache, if we cannot fit a new entry
207 ;;; with max this number of collisions we expand the table (if possible)
208 ;;; and rehash.
209 (defconstant +ctor-table-max-probe-depth+ 5)
210
211 (defun make-ctor-table (size)
212   (declare (index size))
213   (let ((real-size (power-of-two-ceiling size)))
214     (if (< real-size +ctor-table-max-size+)
215         (values (make-array real-size :initial-element nil) nil)
216         (values (make-array +ctor-table-max-size+ :initial-element nil) t))))
217
218 (declaim (inline mix-ctor-hash))
219 (defun mix-ctor-hash (hash base)
220   (logand most-positive-fixnum (+ hash base 1)))
221
222 (defun put-ctor (ctor table)
223   (cond ((try-put-ctor ctor table)
224          (values ctor table))
225         (t
226          (expand-ctor-table ctor table))))
227
228 ;;; Thread-safe: if two threads write to the same index in parallel, the other
229 ;;; result is just lost. This is not an issue as the CTORs are used as their
230 ;;; own keys. If both were EQ, we're good. If non-EQ, the next time the other
231 ;;; one is needed we just cache it again -- hopefully not getting stomped on
232 ;;; that time.
233 (defun try-put-ctor (ctor table)
234   (declare (simple-vector table) (optimize speed))
235   (let* ((class (ctor-class-or-name ctor))
236          (base (sxhash-symbol-or-class class))
237          (hash base)
238          (mask (1- (length table))))
239     (declare (fixnum base hash mask))
240     (loop repeat +ctor-table-max-probe-depth+
241           do (let* ((index (logand mask hash))
242                     (old (aref table index)))
243                (cond ((and old (neq class (ctor-class-or-name old)))
244                       (setf hash (mix-ctor-hash hash base)))
245                      (t
246                       (setf (aref table index) ctor)
247                       (return-from try-put-ctor t)))))
248     ;; Didn't fit, must expand
249     nil))
250
251 (defun get-ctor (class table)
252   (declare (simple-vector table) (optimize speed))
253   (let* ((base (sxhash-symbol-or-class class))
254          (hash base)
255          (mask (1- (length table))))
256     (declare (fixnum base hash mask))
257     (loop repeat +ctor-table-max-probe-depth+
258           do (let* ((index (logand mask hash))
259                     (old (aref table index)))
260                (if (and old (eq class (ctor-class-or-name old)))
261                    (return-from get-ctor old)
262                    (setf hash (mix-ctor-hash hash base)))))
263     ;; Nothing.
264     nil))
265
266 ;;; Thread safe: the old table is read, but if another thread mutates
267 ;;; it while we're reading we still get a sane result -- either the old
268 ;;; or the new entry. The new table is locally allocated, so that's ok
269 ;;; too.
270 (defun expand-ctor-table (ctor old)
271   (declare (simple-vector old))
272   (let* ((old-size (length old))
273          (new-size (* 2 old-size))
274          (drop-random-entries nil))
275     (tagbody
276      :again
277        (multiple-value-bind (new max-size-p) (make-ctor-table new-size)
278          (let ((action (if drop-random-entries
279                            ;; Same logic as in method caches -- see comment
280                            ;; there.
281                            (randomly-punting-lambda (old-ctor)
282                              (try-put-ctor old-ctor new))
283                            (lambda (old-ctor)
284                              (unless (try-put-ctor old-ctor new)
285                                (if max-size-p
286                                    (setf drop-random-entries t)
287                                    (setf new-size (* 2 new-size)))
288                                (go :again))))))
289            (aver (try-put-ctor ctor new))
290            (dotimes (i old-size)
291              (let ((old-ctor (aref old i)))
292                (when old-ctor
293                  (funcall action old-ctor))))
294            (return-from expand-ctor-table (values ctor new)))))))
295
296 (defun ctor-list-to-table (list)
297   (let ((table (make-ctor-table (length list))))
298     (dolist (ctor list)
299       (setf table (nth-value 1 (put-ctor ctor table))))
300     table))
301
302 (defun ctor-for-caching (class-name initargs safe-code-p)
303   (let ((name (make-ctor-function-name class-name initargs safe-code-p)))
304     (or (ensure-ctor name class-name initargs safe-code-p)
305         (fdefinition name))))
306
307 (defun ensure-cached-ctor (class-name store initargs safe-code-p)
308   (if (listp store)
309       (multiple-value-bind (ctor list) (find-ctor class-name store)
310         (if ctor
311             (values ctor list)
312             (let ((ctor (ctor-for-caching class-name initargs safe-code-p)))
313               (if (< (length list) +ctor-list-max-size+)
314                   (values ctor (cons ctor list))
315                   (values ctor (ctor-list-to-table list))))))
316       (let ((ctor (get-ctor class-name store)))
317         (if ctor
318             (values ctor store)
319             (put-ctor (ctor-for-caching class-name initargs safe-code-p)
320                       store)))))
321 \f
322 ;;; ***********************************************
323 ;;; Compile-Time Expansion of MAKE-INSTANCE *******
324 ;;; ***********************************************
325
326 (defvar *compiling-optimized-constructor* nil)
327
328 (define-compiler-macro make-instance (&whole form &rest args &environment env)
329   (declare (ignore args))
330   ;; Compiling an optimized constructor for a non-standard class means compiling a
331   ;; lambda with (MAKE-INSTANCE #<SOME-CLASS X> ...) in it -- need
332   ;; to make sure we don't recurse there.
333   (or (unless *compiling-optimized-constructor*
334         (make-instance->constructor-call form (safe-code-p env)))
335       form))
336
337 (defun make-instance->constructor-call (form safe-code-p)
338   (destructuring-bind (class-arg &rest args) (cdr form)
339     (flet (;;
340            ;; Return the name of parameter number I of a constructor
341            ;; function.
342            (parameter-name (i)
343              (let ((ps #(.p0. .p1. .p2. .p3. .p4. .p5.)))
344                (if (array-in-bounds-p ps i)
345                    (aref ps i)
346                    (format-symbol *pcl-package* ".P~D." i))))
347            ;; Check if CLASS-ARG is a constant symbol.  Give up if
348            ;; not.
349            (constant-class-p ()
350              (and class-arg (constant-class-arg-p class-arg)))
351            ;; Check if ARGS are suitable for an optimized constructor.
352            ;; Return NIL from the outer function if not.
353            (check-args ()
354              (loop for (key . more) on args by #'cddr do
355                       (when (or (null more)
356                                 (not (constant-symbol-p key))
357                                 (eq :allow-other-keys (constant-form-value key)))
358                         (return-from make-instance->constructor-call nil)))))
359       (check-args)
360       ;; Collect a plist of initargs and constant values/parameter names
361       ;; in INITARGS.  Collect non-constant initialization forms in
362       ;; VALUE-FORMS.
363       (multiple-value-bind (initargs value-forms)
364           (loop for (key value) on args by #'cddr and i from 0
365                 collect (constant-form-value key) into initargs
366                 if (constantp value)
367                 collect value into initargs
368                 else
369                 collect (parameter-name i) into initargs
370                 and collect value into value-forms
371                 finally
372                 (return (values initargs value-forms)))
373         (if (constant-class-p)
374             (let* ((class-or-name (constant-form-value class-arg))
375                    (function-name (make-ctor-function-name class-or-name initargs
376                                                            safe-code-p)))
377               ;; Prevent compiler warnings for calling the ctor.
378               (proclaim-as-fun-name function-name)
379               (note-name-defined function-name :function)
380               (when (eq (info :function :where-from function-name) :assumed)
381                 (setf (info :function :where-from function-name) :defined)
382                 (when (info :function :assumed-type function-name)
383                   (setf (info :function :assumed-type function-name) nil)))
384               ;; Return code constructing a ctor at load time, which, when
385               ;; called, will set its funcallable instance function to an
386               ;; optimized constructor function.
387               `(locally
388                    (declare (disable-package-locks ,function-name))
389                  (let ((.x. (load-time-value
390                              (ensure-ctor ',function-name ',class-or-name ',initargs
391                                           ',safe-code-p))))
392                    (declare (ignore .x.))
393                    ;; ??? check if this is worth it.
394                    (declare
395                     (ftype (or (function ,(make-list (length value-forms)
396                                                      :initial-element t)
397                                          t)
398                                (function (&rest t) t))
399                            ,function-name))
400                    (funcall (function ,function-name) ,@value-forms))))
401             (when class-arg
402               ;; Build an inline cache: a CONS, with the actual cache in the CDR.
403               `(locally (declare (disable-package-locks .cache. .class-arg. .store. .fun.
404                                                         make-instance))
405                  (let* ((.cache. (load-time-value (cons 'ctor-cache nil)))
406                         (.store. (cdr .cache.))
407                         (.class-arg. ,class-arg))
408                    (multiple-value-bind (.fun. .new-store.)
409                        (ensure-cached-ctor .class-arg. .store. ',initargs ',safe-code-p)
410                      ;; Thread safe: if multiple threads hit this in paralle, the update
411                      ;; from the other one is just lost -- no harm done, except for the
412                      ;; need to redo the work next time.
413                      (unless (eq .store. .new-store.)
414                        (setf (cdr .cache.) .new-store.))
415                      (funcall (truly-the function .fun.) ,@value-forms))))))))))
416 \f
417 ;;; **************************************************
418 ;;; Load-Time Constructor Function Generation  *******
419 ;;; **************************************************
420
421 ;;; The system-supplied primary INITIALIZE-INSTANCE and
422 ;;; SHARED-INITIALIZE methods.  One cannot initialize these variables
423 ;;; to the right values here because said functions don't exist yet
424 ;;; when this file is first loaded.
425 (defvar *the-system-ii-method* nil)
426 (defvar *the-system-si-method* nil)
427
428 (defun install-optimized-constructor (ctor)
429   (with-world-lock ()
430     (let* ((class-or-name (ctor-class-or-name ctor))
431            (class (if (symbolp class-or-name)
432                       (find-class class-or-name)
433                       class-or-name)))
434       (unless (class-finalized-p class)
435         (finalize-inheritance class))
436       ;; We can have a class with an invalid layout here.  Such a class
437       ;; cannot have a LAYOUT-INVALID of (:FLUSH ...) or (:OBSOLETE
438       ;; ...), because part of the deal is that those only happen from
439       ;; FORCE-CACHE-FLUSHES, which create a new valid wrapper for the
440       ;; class.  An invalid layout of T needs to be flushed, however.
441       (when (eq (layout-invalid (class-wrapper class)) t)
442         (%force-cache-flushes class))
443       (setf (ctor-class ctor) class)
444       (pushnew ctor (plist-value class 'ctors) :test #'eq)
445       (setf (funcallable-instance-fun ctor)
446             (multiple-value-bind (form locations names)
447                 (constructor-function-form ctor)
448               (apply
449                (let ((*compiling-optimized-constructor* t))
450                  (compile nil `(lambda ,names ,form)))
451                locations))))))
452
453 (defun constructor-function-form (ctor)
454   (let* ((class (ctor-class ctor))
455          (proto (class-prototype class))
456          (make-instance-methods
457           (compute-applicable-methods #'make-instance (list class)))
458          (allocate-instance-methods
459           (compute-applicable-methods #'allocate-instance (list class)))
460          ;; I stared at this in confusion for a while, thinking
461          ;; carefully about the possibility of the class prototype not
462          ;; being of sufficient discrimiating power, given the
463          ;; possibility of EQL-specialized methods on
464          ;; INITIALIZE-INSTANCE or SHARED-INITIALIZE.  However, given
465          ;; that this is a constructor optimization, the user doesn't
466          ;; yet have the instance to create a method with such an EQL
467          ;; specializer.
468          ;;
469          ;; There remains the (theoretical) possibility of someone
470          ;; coming along with code of the form
471          ;;
472          ;; (defmethod initialize-instance :before ((o foo) ...)
473          ;;   (eval `(defmethod shared-initialize :before ((o foo) ...) ...)))
474          ;;
475          ;; but probably we can afford not to worry about this too
476          ;; much for now.  -- CSR, 2004-07-12
477          (ii-methods
478           (compute-applicable-methods #'initialize-instance (list proto)))
479          (si-methods
480           (compute-applicable-methods #'shared-initialize (list proto t)))
481          (setf-svuc-slots-methods
482           (loop for slot in (class-slots class)
483                 collect (compute-applicable-methods
484                          #'(setf slot-value-using-class)
485                          (list nil class proto slot))))
486          (sbuc-slots-methods
487           (loop for slot in (class-slots class)
488                 collect (compute-applicable-methods
489                          #'slot-boundp-using-class
490                          (list class proto slot)))))
491     ;; Cannot initialize these variables earlier because the generic
492     ;; functions don't exist when PCL is built.
493     (when (null *the-system-si-method*)
494       (setq *the-system-si-method*
495             (find-method #'shared-initialize
496                          () (list *the-class-slot-object* *the-class-t*)))
497       (setq *the-system-ii-method*
498             (find-method #'initialize-instance
499                          () (list *the-class-slot-object*))))
500     ;; Note that when there are user-defined applicable methods on
501     ;; MAKE-INSTANCE and/or ALLOCATE-INSTANCE, these will show up
502     ;; together with the system-defined ones in what
503     ;; COMPUTE-APPLICABLE-METHODS returns.
504     (if (and (not (structure-class-p class))
505              (not (condition-class-p class))
506              (null (cdr make-instance-methods))
507              (null (cdr allocate-instance-methods))
508              (every (lambda (x)
509                       (member (slot-definition-allocation x)
510                               '(:instance :class)))
511                     (class-slots class))
512              (null (check-initargs-1
513                     class
514                     (append
515                      (ctor-default-initkeys
516                       (ctor-initargs ctor) (class-default-initargs class))
517                      (plist-keys (ctor-initargs ctor)))
518                     (append ii-methods si-methods) nil nil))
519              (not (around-or-nonstandard-primary-method-p
520                    ii-methods *the-system-ii-method*))
521              (not (around-or-nonstandard-primary-method-p
522                    si-methods *the-system-si-method*))
523              ;; the instance structure protocol goes through
524              ;; slot-value(-using-class) and friends (actually just
525              ;; (SETF SLOT-VALUE-USING-CLASS) and
526              ;; SLOT-BOUNDP-USING-CLASS), so if there are non-standard
527              ;; applicable methods we can't shortcircuit them.
528              (every (lambda (x) (= (length x) 1)) setf-svuc-slots-methods)
529              (every (lambda (x) (= (length x) 1)) sbuc-slots-methods))
530         (optimizing-generator ctor ii-methods si-methods)
531         (fallback-generator ctor ii-methods si-methods))))
532
533 (defun around-or-nonstandard-primary-method-p
534     (methods &optional standard-method)
535   (loop with primary-checked-p = nil
536         for method in methods
537         as qualifiers = (if (consp method)
538                             (early-method-qualifiers method)
539                             (safe-method-qualifiers method))
540         when (or (eq :around (car qualifiers))
541                  (and (null qualifiers)
542                       (not primary-checked-p)
543                       (not (null standard-method))
544                       (not (eq standard-method method))))
545           return t
546         when (null qualifiers) do
547           (setq primary-checked-p t)))
548
549 (defun fallback-generator (ctor ii-methods si-methods)
550   (declare (ignore ii-methods si-methods))
551   `(lambda ,(make-ctor-parameter-list ctor)
552      ;; The CTOR MAKE-INSTANCE optimization only kicks in when the
553      ;; first argument to MAKE-INSTANCE is a constant symbol: by
554      ;; calling it with a class, as here, we inhibit the optimization,
555      ;; so removing the possibility of endless recursion.  -- CSR,
556      ;; 2004-07-12
557      (make-instance ,(ctor-class ctor)
558       ,@(quote-plist-keys (ctor-initargs ctor)))))
559
560 (defun optimizing-generator (ctor ii-methods si-methods)
561   (multiple-value-bind (locations names body before-method-p)
562       (fake-initialization-emf ctor ii-methods si-methods)
563     (let ((wrapper (class-wrapper (ctor-class ctor))))
564       (values
565        `(lambda ,(make-ctor-parameter-list ctor)
566          (declare #.*optimize-speed*)
567          (block nil
568            (when (layout-invalid ,wrapper)
569              (install-initial-constructor ,ctor)
570              (return (funcall ,ctor ,@(make-ctor-parameter-list ctor))))
571            ,(wrap-in-allocate-forms ctor body before-method-p)))
572        locations
573        names))))
574
575 ;;; Return a form wrapped around BODY that allocates an instance
576 ;;; constructed by CTOR.  BEFORE-METHOD-P set means we have to run
577 ;;; before-methods, in which case we initialize instance slots to
578 ;;; +SLOT-UNBOUND+.  The resulting form binds the local variables
579 ;;; .INSTANCE. to the instance, and .SLOTS. to the instance's slot
580 ;;; vector around BODY.
581 (defun wrap-in-allocate-forms (ctor body before-method-p)
582   (let* ((class (ctor-class ctor))
583          (wrapper (class-wrapper class))
584          (allocation-function (raw-instance-allocator class))
585          (slots-fetcher (slots-fetcher class)))
586     (if (eq allocation-function 'allocate-standard-instance)
587         `(let ((.instance. (%make-standard-instance nil
588                                                     (get-instance-hash-code)))
589                (.slots. (make-array
590                          ,(layout-length wrapper)
591                          ,@(when before-method-p
592                              '(:initial-element +slot-unbound+)))))
593            (setf (std-instance-wrapper .instance.) ,wrapper)
594            (setf (std-instance-slots .instance.) .slots.)
595            ,body
596            .instance.)
597         `(let* ((.instance. (,allocation-function ,wrapper))
598                 (.slots. (,slots-fetcher .instance.)))
599            (declare (ignorable .slots.))
600            ,body
601            .instance.))))
602
603 ;;; Return a form for invoking METHOD with arguments from ARGS.  As
604 ;;; can be seen in METHOD-FUNCTION-FROM-FAST-FUNCTION, method
605 ;;; functions look like (LAMBDA (ARGS NEXT-METHODS) ...).  We could
606 ;;; call fast method functions directly here, but benchmarks show that
607 ;;; there's no speed to gain, so lets avoid the hair here.
608 (defmacro invoke-method (method args)
609   `(funcall ,(method-function method) ,args ()))
610
611 ;;; Return a form that is sort of an effective method comprising all
612 ;;; calls to INITIALIZE-INSTANCE and SHARED-INITIALIZE that would
613 ;;; normally have taken place when calling MAKE-INSTANCE.
614 (defun fake-initialization-emf (ctor ii-methods si-methods)
615   (multiple-value-bind (ii-around ii-before ii-primary ii-after)
616       (standard-sort-methods ii-methods)
617     (declare (ignore ii-primary))
618     (multiple-value-bind (si-around si-before si-primary si-after)
619         (standard-sort-methods si-methods)
620       (declare (ignore si-primary))
621       (aver (and (null ii-around) (null si-around)))
622       (let ((initargs (ctor-initargs ctor)))
623         (multiple-value-bind (locations names bindings vars defaulting-initargs body)
624             (slot-init-forms ctor (or ii-before si-before))
625         (values
626          locations
627          names
628          `(let ,bindings
629            (declare (ignorable ,@vars))
630            (let (,@(when (or ii-before ii-after)
631                      `((.ii-args.
632                         (list .instance. ,@(quote-plist-keys initargs) ,@defaulting-initargs))))
633                  ,@(when (or si-before si-after)
634                      `((.si-args.
635                         (list .instance. t ,@(quote-plist-keys initargs) ,@defaulting-initargs)))))
636             ,@(loop for method in ii-before
637                     collect `(invoke-method ,method .ii-args.))
638             ,@(loop for method in si-before
639                     collect `(invoke-method ,method .si-args.))
640             ,@body
641             ,@(loop for method in si-after
642                     collect `(invoke-method ,method .si-args.))
643             ,@(loop for method in ii-after
644                     collect `(invoke-method ,method .ii-args.))))
645          (or ii-before si-before)))))))
646
647 ;;; Return four values from APPLICABLE-METHODS: around methods, before
648 ;;; methods, the applicable primary method, and applicable after
649 ;;; methods.  Before and after methods are sorted in the order they
650 ;;; must be called.
651 (defun standard-sort-methods (applicable-methods)
652   (loop for method in applicable-methods
653         as qualifiers = (if (consp method)
654                             (early-method-qualifiers method)
655                             (safe-method-qualifiers method))
656         if (null qualifiers)
657           collect method into primary
658         else if (eq :around (car qualifiers))
659           collect method into around
660         else if (eq :after (car qualifiers))
661           collect method into after
662         else if (eq :before (car qualifiers))
663           collect method into before
664         finally
665           (return (values around before (first primary) (reverse after)))))
666
667 (defmacro with-type-checked ((type safe-p) &body body)
668   (if safe-p
669       ;; To handle FUNCTION types reasonable, we use SAFETY 3 and
670       ;; THE instead of e.g. CHECK-TYPE.
671       `(locally
672            (declare (optimize (safety 3)))
673          (the ,type (progn ,@body)))
674       `(progn ,@body)))
675
676 ;;; Return as multiple values bindings for default initialization
677 ;;; arguments, variable names, defaulting initargs and a body for
678 ;;; initializing instance and class slots of an object costructed by
679 ;;; CTOR.  The variable .SLOTS. is assumed to bound to the instance's
680 ;;; slot vector.  BEFORE-METHOD-P T means before-methods will be
681 ;;; called, which means that 1) other code will initialize instance
682 ;;; slots to +SLOT-UNBOUND+ before the before-methods are run, and
683 ;;; that we have to check if these before-methods have set slots.
684 (defun slot-init-forms (ctor before-method-p)
685   (let* ((class (ctor-class ctor))
686          (initargs (ctor-initargs ctor))
687          (initkeys (plist-keys initargs))
688          (safe-p (ctor-safe-p ctor))
689          (slot-vector
690           (make-array (layout-length (class-wrapper class))
691                       :initial-element nil))
692          (class-inits ())
693          (default-inits ())
694          (defaulting-initargs ())
695          (default-initargs (class-default-initargs class))
696          (initarg-locations
697           (compute-initarg-locations
698            class (append initkeys (mapcar #'car default-initargs)))))
699     (labels ((initarg-locations (initarg)
700                (cdr (assoc initarg initarg-locations :test #'eq)))
701              (initializedp (location)
702                (cond
703                  ((consp location)
704                   (assoc location class-inits :test #'eq))
705                  ((integerp location)
706                   (not (null (aref slot-vector location))))
707                  (t (bug "Weird location in ~S" 'slot-init-forms))))
708              (class-init (location kind val type)
709                (aver (consp location))
710                (unless (initializedp location)
711                  (push (list location kind val type) class-inits)))
712              (instance-init (location kind val type)
713                (aver (integerp location))
714                (unless (initializedp location)
715                  (setf (aref slot-vector location) (list kind val type))))
716              (default-init-var-name (i)
717                (let ((ps #(.d0. .d1. .d2. .d3. .d4. .d5.)))
718                  (if (array-in-bounds-p ps i)
719                      (aref ps i)
720                      (format-symbol *pcl-package* ".D~D." i))))
721              (location-var-name (i)
722                (let ((ls #(.l0. .l1. .l2. .l3. .l4. .l5.)))
723                  (if (array-in-bounds-p ls i)
724                      (aref ls i)
725                      (format-symbol *pcl-package* ".L~D." i)))))
726       ;; Loop over supplied initargs and values and record which
727       ;; instance and class slots they initialize.
728       (loop for (key value) on initargs by #'cddr
729             as kind = (if (constantp value) 'constant 'param)
730             as locations = (initarg-locations key)
731             do (loop for (location . type) in locations
732                      do (if (consp location)
733                             (class-init location kind value type)
734                             (instance-init location kind value type))))
735       ;; Loop over default initargs of the class, recording
736       ;; initializations of slots that have not been initialized
737       ;; above.  Default initargs which are not in the supplied
738       ;; initargs are treated as if they were appended to supplied
739       ;; initargs, that is, their values must be evaluated even
740       ;; if not actually used for initializing a slot.
741       (loop for (key initform initfn) in default-initargs and i from 0
742             unless (member key initkeys :test #'eq)
743             do (let* ((kind (if (constantp initform) 'constant 'var))
744                       (init (if (eq kind 'var) initfn initform)))
745                  (ecase kind
746                    (constant
747                     (push (list 'quote key) defaulting-initargs)
748                     (push initform defaulting-initargs))
749                    (var
750                     (push (list 'quote key) defaulting-initargs)
751                     (push (default-init-var-name i) defaulting-initargs)))
752               (when (eq kind 'var)
753                 (let ((init-var (default-init-var-name i)))
754                   (setq init init-var)
755                   (push (cons init-var initfn) default-inits)))
756               (loop for (location . type) in (initarg-locations key)
757                     do (if (consp location)
758                            (class-init location kind init type)
759                            (instance-init location kind init type)))))
760       ;; Loop over all slots of the class, filling in the rest from
761       ;; slot initforms.
762       (loop for slotd in (class-slots class)
763             as location = (slot-definition-location slotd)
764             as type = (slot-definition-type slotd)
765             as allocation = (slot-definition-allocation slotd)
766             as initfn = (slot-definition-initfunction slotd)
767             as initform = (slot-definition-initform slotd) do
768               (unless (or (eq allocation :class)
769                           (null initfn)
770                           (initializedp location))
771                 (if (constantp initform)
772                     (instance-init location 'initform initform type)
773                     (instance-init location 'initform/initfn initfn type))))
774       ;; Generate the forms for initializing instance and class slots.
775       (let ((instance-init-forms
776              (loop for slot-entry across slot-vector and i from 0
777                    as (kind value type) = slot-entry collect
778                      (ecase kind
779                        ((nil)
780                         (unless before-method-p
781                           `(setf (clos-slots-ref .slots. ,i) +slot-unbound+)))
782                        ((param var)
783                         `(setf (clos-slots-ref .slots. ,i)
784                                (with-type-checked (,type ,safe-p)
785                                    ,value)))
786                        (initfn
787                         `(setf (clos-slots-ref .slots. ,i)
788                                (with-type-checked (,type ,safe-p)
789                                  (funcall ,value))))
790                        (initform/initfn
791                         (if before-method-p
792                             `(when (eq (clos-slots-ref .slots. ,i)
793                                        +slot-unbound+)
794                                (setf (clos-slots-ref .slots. ,i)
795                                      (with-type-checked (,type ,safe-p)
796                                        (funcall ,value))))
797                             `(setf (clos-slots-ref .slots. ,i)
798                                    (with-type-checked (,type ,safe-p)
799                                      (funcall ,value)))))
800                        (initform
801                         (if before-method-p
802                             `(when (eq (clos-slots-ref .slots. ,i)
803                                        +slot-unbound+)
804                                (setf (clos-slots-ref .slots. ,i)
805                                      (with-type-checked (,type ,safe-p)
806                                        ',(constant-form-value value))))
807                             `(setf (clos-slots-ref .slots. ,i)
808                                    (with-type-checked (,type ,safe-p)
809                                      ',(constant-form-value value)))))
810                        (constant
811                         `(setf (clos-slots-ref .slots. ,i)
812                                (with-type-checked (,type ,safe-p)
813                                  ',(constant-form-value value))))))))
814         ;; we are not allowed to modify QUOTEd locations, so we can't
815         ;; generate code like (setf (cdr ',location) arg).  Instead,
816         ;; we have to do (setf (cdr .L0.) arg) and arrange for .L0. to
817         ;; be bound to the location.
818         (multiple-value-bind (names locations class-init-forms)
819             (loop for (location kind value type) in class-inits
820                   for i upfrom 0
821                   for name = (location-var-name i)
822                   collect name into names
823                   collect location into locations
824                   collect `(setf (cdr ,name)
825                                  (with-type-checked (,type ,safe-p)
826                                    ,(case kind
827                                           (constant `',(constant-form-value value))
828                                           ((param var) `,value)
829                                           (initfn `(funcall ,value)))))
830                   into class-init-forms
831                   finally (return (values names locations class-init-forms)))
832           (multiple-value-bind (vars bindings)
833               (loop for (var . initfn) in (nreverse default-inits)
834                     collect var into vars
835                     collect `(,var (funcall ,initfn)) into bindings
836                     finally (return (values vars bindings)))
837             (values locations names
838                     bindings vars
839                     (nreverse defaulting-initargs)
840                     `(,@(delete nil instance-init-forms)
841                       ,@class-init-forms))))))))
842
843 ;;; Return an alist of lists (KEY (LOCATION . TYPE-SPECIFIER) ...)
844 ;;; telling, for each key in INITKEYS, which locations the initarg
845 ;;; initializes and the associated type with the location.  CLASS is
846 ;;; the class of the instance being initialized.
847 (defun compute-initarg-locations (class initkeys)
848   (loop with slots = (class-slots class)
849         for key in initkeys collect
850           (loop for slot in slots
851                 if (memq key (slot-definition-initargs slot))
852                   collect (cons (slot-definition-location slot)
853                                 (slot-definition-type slot))
854                           into locations
855                 else
856                   collect slot into remaining-slots
857                 finally
858                   (setq slots remaining-slots)
859                   (return (cons key locations)))))
860
861 \f
862 ;;; *******************************
863 ;;; External Entry Points  ********
864 ;;; *******************************
865
866 (defun update-ctors (reason &key class name generic-function method)
867   (labels ((reset (class &optional ri-cache-p (ctorsp t))
868              (when ctorsp
869                (dolist (ctor (plist-value class 'ctors))
870                  (install-initial-constructor ctor)))
871              (when ri-cache-p
872                (setf (plist-value class 'ri-initargs) ()))
873              (dolist (subclass (class-direct-subclasses class))
874                (reset subclass ri-cache-p ctorsp))))
875     (ecase reason
876       ;; CLASS must have been specified.
877       (finalize-inheritance
878        (reset class t))
879       ;; NAME must have been specified.
880       (setf-find-class
881        (loop for ctor in *all-ctors*
882              when (eq (ctor-class-or-name ctor) name) do
883              (when (ctor-class ctor)
884                (reset (ctor-class ctor)))
885              (loop-finish)))
886       ;; GENERIC-FUNCTION and METHOD must have been specified.
887       ((add-method remove-method)
888        (flet ((class-of-1st-method-param (method)
889                 (type-class (first (method-specializers method)))))
890          (case (generic-function-name generic-function)
891            ((make-instance allocate-instance
892              initialize-instance shared-initialize)
893             (reset (class-of-1st-method-param method) t t))
894            ((reinitialize-instance)
895             (reset (class-of-1st-method-param method) t nil))
896            (t (when (or (eq (generic-function-name generic-function)
897                             'slot-boundp-using-class)
898                         (equal (generic-function-name generic-function)
899                                '(setf slot-value-using-class)))
900                 ;; this looks awfully expensive, but given that one
901                 ;; can specialize on the SLOTD argument, nothing is
902                 ;; safe.  -- CSR, 2004-07-12
903                 (reset (find-class 'standard-object))))))))))
904
905 (defun precompile-ctors ()
906   (dolist (ctor *all-ctors*)
907     (when (null (ctor-class ctor))
908       (let ((class (find-class (ctor-class-or-name ctor) nil)))
909         (when (and class (class-finalized-p class))
910           (install-optimized-constructor ctor))))))
911
912 (defun check-ri-initargs (instance initargs)
913   (let* ((class (class-of instance))
914          (keys (plist-keys initargs))
915          (cached (assoc keys (plist-value class 'ri-initargs)
916                         :test #'equal))
917          (invalid-keys
918           (if (consp cached)
919               (cdr cached)
920               (let ((invalid
921                      ;; FIXME: give CHECK-INITARGS-1 and friends a
922                      ;; more mnemonic name and (possibly) a nicer,
923                      ;; more orthogonal interface.
924                      (check-initargs-1
925                       class initargs
926                       (list (list* 'reinitialize-instance instance initargs)
927                             (list* 'shared-initialize instance nil initargs))
928                       t nil)))
929                 (setf (plist-value class 'ri-initargs)
930                       (acons keys invalid cached))
931                 invalid))))
932     (when invalid-keys
933       (error 'initarg-error :class class :initargs invalid-keys))))
934
935 ;;; end of ctor.lisp