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