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