7ed346358ea0df4e01bdc11da4060736ce0ab6af
[sbcl.git] / src / pcl / dlisp.lisp
1 ;;;; This software is part of the SBCL system. See the README file for
2 ;;;; more information.
3
4 ;;;; This software is derived from software originally released by Xerox
5 ;;;; Corporation. Copyright and release statements follow. Later modifications
6 ;;;; to the software are in the public domain and are provided with
7 ;;;; absolutely no warranty. See the COPYING and CREDITS files for more
8 ;;;; information.
9
10 ;;;; copyright information from original PCL sources:
11 ;;;;
12 ;;;; Copyright (c) 1985, 1986, 1987, 1988, 1989, 1990 Xerox Corporation.
13 ;;;; All rights reserved.
14 ;;;;
15 ;;;; Use and copying of this software and preparation of derivative works based
16 ;;;; upon this software are permitted. Any distribution of this software or
17 ;;;; derivative works must comply with all applicable United States export
18 ;;;; control laws.
19 ;;;;
20 ;;;; This software is made available AS IS, and Xerox Corporation makes no
21 ;;;; warranty about the software, its performance or its conformity to any
22 ;;;; specification.
23
24 (in-package "SB-PCL")
25
26 ;;;; some support stuff for getting a hold of symbols that we need when
27 ;;;; building the discriminator codes. It's OK for these to be interned
28 ;;;; symbols because we don't capture any user code in the scope in which
29 ;;;; these symbols are bound.
30
31 (declaim (list *dfun-arg-symbols*))
32 (defvar *dfun-arg-symbols* '(.ARG0. .ARG1. .ARG2. .ARG3.))
33
34 (defun dfun-arg-symbol (arg-number)
35   (or (nth arg-number *dfun-arg-symbols*)
36       (format-symbol *pcl-package* ".ARG~A." arg-number)))
37
38 (declaim (list *slot-vector-symbols*))
39 (defvar *slot-vector-symbols* '(.SLOTS0. .SLOTS1. .SLOTS2. .SLOTS3.))
40
41 (defun slot-vector-symbol (arg-number)
42   (or (nth arg-number *slot-vector-symbols*)
43       (format-symbol *pcl-package* ".SLOTS~A." arg-number)))
44
45 (declaim (inline make-dfun-required-args))
46 (defun make-dfun-required-args (count)
47   (declare (type index count))
48   (let (result)
49     (dotimes (i count (nreverse result))
50       (push (dfun-arg-symbol i) result))))
51
52 (defun make-dfun-lambda-list (nargs applyp)
53   (let ((required (make-dfun-required-args nargs)))
54     (if applyp
55         (nconc required
56                ;; Use &MORE arguments to avoid consing up an &REST list
57                ;; that we might not need at all. See MAKE-EMF-CALL and
58                ;; INVOKE-EFFECTIVE-METHOD-FUNCTION for the other
59                ;; pieces.
60                '(&more .dfun-more-context. .dfun-more-count.))
61         required)))
62
63 (defun make-dlap-lambda-list (nargs applyp)
64   (let* ((required (make-dfun-required-args nargs))
65          (lambda-list (if applyp
66                           (append required '(&more .more-context. .more-count.))
67                           required)))
68     ;; Return the full lambda list, the required arguments, a form
69     ;; that will generate a rest-list, and a list of the &MORE
70     ;; parameters used.
71     (values lambda-list
72             required
73             (when applyp
74               '((sb-c::%listify-rest-args
75                  .more-context.
76                  (the (and unsigned-byte fixnum)
77                    .more-count.))))
78             (when applyp
79               '(.more-context. .more-count.)))))
80
81 (defun make-emf-call (nargs applyp fn-variable &optional emf-type)
82   (let ((required (make-dfun-required-args nargs)))
83     `(,(if (eq emf-type 'fast-method-call)
84            'invoke-effective-method-function-fast
85            'invoke-effective-method-function)
86        ,fn-variable
87        ,applyp
88        :required-args ,required
89        ;; INVOKE-EFFECTIVE-METHOD-FUNCTION will decide whether to use
90        ;; the :REST-ARG version or the :MORE-ARG version depending on
91        ;; the type of the EMF.
92        :rest-arg ,(if applyp
93                       ;; Creates a list from the &MORE arguments.
94                       '((sb-c::%listify-rest-args
95                          .dfun-more-context.
96                          (the (and unsigned-byte fixnum)
97                            .dfun-more-count.)))
98                       nil)
99        :more-arg ,(when applyp
100                     '(.dfun-more-context. .dfun-more-count.)))))
101
102 (defun make-fast-method-call-lambda-list (nargs applyp)
103   (list* '.pv-cell. '.next-method-call. (make-dfun-lambda-list nargs applyp)))
104 \f
105 ;;; Emitting various accessors.
106
107 (defun emit-one-class-reader (class-slot-p)
108   (emit-reader/writer :reader 1 class-slot-p))
109
110 (defun emit-one-class-boundp (class-slot-p)
111   (emit-reader/writer :boundp 1 class-slot-p))
112
113 (defun emit-one-class-writer (class-slot-p)
114   (emit-reader/writer :writer 1 class-slot-p))
115
116 (defun emit-two-class-reader (class-slot-p)
117   (emit-reader/writer :reader 2 class-slot-p))
118
119 (defun emit-two-class-boundp (class-slot-p)
120   (emit-reader/writer :boundp 2 class-slot-p))
121
122 (defun emit-two-class-writer (class-slot-p)
123   (emit-reader/writer :writer 2 class-slot-p))
124
125 ;;; --------------------------------
126
127 (defun emit-one-index-readers (class-slot-p)
128   (emit-one-or-n-index-reader/writer :reader nil class-slot-p))
129
130 (defun emit-one-index-boundps (class-slot-p)
131   (emit-one-or-n-index-reader/writer :boundp nil class-slot-p))
132
133 (defun emit-one-index-writers (class-slot-p)
134   (emit-one-or-n-index-reader/writer :writer nil class-slot-p))
135
136 (defun emit-n-n-readers ()
137   (emit-one-or-n-index-reader/writer :reader t nil))
138
139 (defun emit-n-n-boundps ()
140   (emit-one-or-n-index-reader/writer :boundp t nil))
141
142 (defun emit-n-n-writers ()
143   (emit-one-or-n-index-reader/writer :writer t nil))
144
145 ;;; --------------------------------
146
147 (defun emit-checking (metatypes applyp)
148   (emit-checking-or-caching nil nil metatypes applyp))
149
150 (defun emit-caching (metatypes applyp)
151   (emit-checking-or-caching t nil metatypes applyp))
152
153 (defun emit-in-checking-cache-p (metatypes)
154   (emit-checking-or-caching nil t metatypes nil))
155
156 (defun emit-constant-value (metatypes)
157   (emit-checking-or-caching t t metatypes nil))
158
159 ;;; --------------------------------
160
161 ;;; FIXME: What do these variables mean?
162 (defvar *precompiling-lap* nil)
163 (defvar *emit-function-p* t)
164
165 ;;; FIXME: This variable is motivated by Gerd Moellman's observation,
166 ;;; in <867kga1wra.fsf@gerd.free-bsd.org> on cmucl-imp 2002-10-22,
167 ;;; that the functions returned from EMIT-xxx-FUNCTION can cause an
168 ;;; order-of-magnitude slowdown.  We include this variable for now,
169 ;;; but maybe its effect should rather be controlled by compilation
170 ;;; policy if there is a noticeable space difference between the
171 ;;; branches, or else maybe the EMIT-xxx-FUNCTION branches should be
172 ;;; deleted.  It's not clear to me how all of this works, though, so
173 ;;; until proper benchmarks are done it's probably safest simply to
174 ;;; have this pseudo-constant to hide code.  -- CSR, 2003-02-14
175 (defvar *optimize-cache-functions-p* t)
176
177 (defun emit-default-only (metatypes applyp)
178   (unless *optimize-cache-functions-p*
179     (when (and (null *precompiling-lap*) *emit-function-p*)
180       (return-from emit-default-only
181         (emit-default-only-function metatypes applyp))))
182   (multiple-value-bind (lambda-list args rest-arg more-arg)
183       (make-dlap-lambda-list (length metatypes) applyp)
184     (generating-lisp '(emf)
185                      lambda-list
186                      `(invoke-effective-method-function emf
187                                                         ,applyp
188                                                         :required-args ,args
189                                                         :more-arg ,more-arg
190                                                         :rest-arg ,rest-arg))))
191
192 ;;; --------------------------------
193
194 (defun generating-lisp (closure-variables args form)
195   (let ((lambda `(lambda ,closure-variables
196                    ,@(when (member 'miss-fn closure-variables)
197                            `((declare (type function miss-fn))))
198                    #'(lambda ,args
199                        (let ()
200                          (declare #.*optimize-speed*)
201                          ,form)))))
202     (values (if *precompiling-lap*
203                 `#',lambda
204                 (compile nil lambda))
205             nil)))
206
207 ;;; note on implementation for CMU 17 and later (including SBCL):
208 ;;; Since STD-INSTANCE-P is weakened, that branch may run on non-PCL
209 ;;; instances (structures). The result will be the non-wrapper layout
210 ;;; for the structure, which will cause a miss. The "slots" will be
211 ;;; whatever the first slot is, but will be ignored. Similarly,
212 ;;; FSC-INSTANCE-P returns true on funcallable structures as well as
213 ;;; PCL fins.
214 (defun emit-reader/writer (reader/writer 1-or-2-class class-slot-p)
215   (unless *optimize-cache-functions-p*
216     (when (and (null *precompiling-lap*) *emit-function-p*)
217       (return-from emit-reader/writer
218         (emit-reader/writer-function
219          reader/writer 1-or-2-class class-slot-p))))
220   (let ((instance nil)
221         (arglist  ())
222         (closure-variables ())
223         (read-form (emit-slot-read-form class-slot-p 'index 'slots)))
224     (ecase reader/writer
225       ((:reader :boundp)
226        (setq instance (dfun-arg-symbol 0)
227              arglist  (list instance)))
228       (:writer (setq instance (dfun-arg-symbol 1)
229                      arglist  (list (dfun-arg-symbol 0) instance))))
230     (ecase 1-or-2-class
231       (1 (setq closure-variables '(wrapper-0 index miss-fn)))
232       (2 (setq closure-variables '(wrapper-0 wrapper-1 index miss-fn))))
233     (generating-lisp
234      closure-variables
235      arglist
236      `(let* (,@(unless class-slot-p `((slots nil)))
237                (wrapper (cond ((std-instance-p ,instance)
238                                ,@(unless class-slot-p
239                                    `((setq slots
240                                            (std-instance-slots ,instance))))
241                                (std-instance-wrapper ,instance))
242                               ((fsc-instance-p ,instance)
243                                ,@(unless class-slot-p
244                                    `((setq slots
245                                            (fsc-instance-slots ,instance))))
246                                (fsc-instance-wrapper ,instance)))))
247         (block access
248           (when (and wrapper
249                      (/= (layout-clos-hash wrapper) 0)
250                      ,@(if (eql 1 1-or-2-class)
251                            `((eq wrapper wrapper-0))
252                            `((or (eq wrapper wrapper-0)
253                                  (eq wrapper wrapper-1)))))
254             ,@(ecase reader/writer
255                 (:reader
256                  `((let ((value ,read-form))
257                      (unless (eq value +slot-unbound+)
258                        (return-from access value)))))
259                 (:boundp
260                  `((let ((value ,read-form))
261                      (return-from access (not (eq value +slot-unbound+))))))
262                 (:writer
263                  `((return-from access (setf ,read-form ,(car arglist)))))))
264           (funcall miss-fn ,@arglist))))))
265
266 (defun emit-slot-read-form (class-slot-p index slots)
267   (if class-slot-p
268       `(cdr ,index)
269       `(clos-slots-ref ,slots ,index)))
270
271 (defun emit-boundp-check (value-form miss-fn arglist)
272   `(let ((value ,value-form))
273      (if (eq value +slot-unbound+)
274          (funcall ,miss-fn ,@arglist)
275          value)))
276
277 (defun emit-slot-access (reader/writer class-slot-p slots
278                          index miss-fn arglist)
279   (let ((read-form (emit-slot-read-form class-slot-p index slots)))
280     (ecase reader/writer
281       (:reader (emit-boundp-check read-form miss-fn arglist))
282       (:boundp `(not (eq ,read-form +slot-unbound+)))
283       (:writer `(setf ,read-form ,(car arglist))))))
284
285 (defmacro emit-reader/writer-macro (reader/writer 1-or-2-class class-slot-p)
286   (let ((*emit-function-p* nil)
287         (*precompiling-lap* t))
288     (values
289      (emit-reader/writer reader/writer 1-or-2-class class-slot-p))))
290
291 (defun emit-one-or-n-index-reader/writer (reader/writer
292                                           cached-index-p
293                                           class-slot-p)
294   (unless *optimize-cache-functions-p*
295     (when (and (null *precompiling-lap*) *emit-function-p*)
296       (return-from emit-one-or-n-index-reader/writer
297         (emit-one-or-n-index-reader/writer-function
298          reader/writer cached-index-p class-slot-p))))
299   (multiple-value-bind (arglist metatypes)
300       (ecase reader/writer
301         ((:reader :boundp)
302          (values (list (dfun-arg-symbol 0))
303                  '(standard-instance)))
304         (:writer (values (list (dfun-arg-symbol 0) (dfun-arg-symbol 1))
305                          '(t standard-instance))))
306     (generating-lisp
307      `(cache ,@(unless cached-index-p '(index)) miss-fn)
308      arglist
309      `(let (,@(unless class-slot-p '(slots))
310             ,@(when cached-index-p '(index)))
311         ,(emit-dlap 'cache arglist metatypes
312                     (emit-slot-access reader/writer class-slot-p
313                                       'slots 'index 'miss-fn arglist)
314                     `(funcall miss-fn ,@arglist)
315                     (when cached-index-p 'index)
316                     (unless class-slot-p '(slots)))))))
317
318 (defmacro emit-one-or-n-index-reader/writer-macro
319     (reader/writer cached-index-p class-slot-p)
320   (let ((*emit-function-p* nil)
321         (*precompiling-lap* t))
322     (values
323      (emit-one-or-n-index-reader/writer reader/writer
324                                         cached-index-p
325                                         class-slot-p))))
326
327 (defun emit-miss (miss-fn args applyp)
328   (if applyp
329       `(multiple-value-call ,miss-fn ,@args
330                             (sb-c::%more-arg-values .more-context.
331                                                     0
332                                                     .more-count.))
333       `(funcall ,miss-fn ,@args)))
334
335 (defun emit-checking-or-caching (cached-emf-p return-value-p metatypes applyp)
336   (unless *optimize-cache-functions-p*
337     (when (and (null *precompiling-lap*) *emit-function-p*)
338       (return-from emit-checking-or-caching
339         (emit-checking-or-caching-function
340          cached-emf-p return-value-p metatypes applyp))))
341   (multiple-value-bind (lambda-list args rest-arg more-arg)
342       (make-dlap-lambda-list (length metatypes) applyp)
343     (generating-lisp
344      `(cache ,@(unless cached-emf-p '(emf)) miss-fn)
345      lambda-list
346      `(let (,@(when cached-emf-p '(emf)))
347         ,(emit-dlap 'cache args metatypes
348                     (if return-value-p
349                         (if cached-emf-p 'emf t)
350                         `(invoke-effective-method-function
351                           emf ,applyp
352                           :required-args ,args
353                           :more-arg ,more-arg
354                           :rest-arg ,rest-arg))
355                     (emit-miss 'miss-fn args applyp)
356                     (when cached-emf-p 'emf))))))
357
358 (defmacro emit-checking-or-caching-macro (cached-emf-p
359                                           return-value-p
360                                           metatypes
361                                           applyp)
362   (let ((*emit-function-p* nil)
363         (*precompiling-lap* t))
364     (values
365      (emit-checking-or-caching cached-emf-p return-value-p metatypes applyp))))
366
367 (defun emit-dlap (cache-var args metatypes hit-form miss-form value-var
368                   &optional slot-vars)
369   (let* ((index -1)
370          (miss-tag (gensym "MISSED"))
371          (wrapper-bindings (mapcan (lambda (arg mt)
372                                      (unless (eq mt t)
373                                        (incf index)
374                                        `((,(format-symbol *pcl-package*
375                                                           "WRAPPER-~D"
376                                                           index)
377                                           ,(emit-fetch-wrapper
378                                             mt arg miss-tag (pop slot-vars))))))
379                                    args metatypes))
380          (wrapper-vars (mapcar #'car wrapper-bindings)))
381     (declare (fixnum index))
382     (unless wrapper-vars
383       (error "Every metatype is T."))
384     `(prog ()
385         (return
386           (let ((cache-vector (cache-vector ,cache-var))
387                 (mask (cache-mask ,cache-var))
388                 (size (cache-size ,cache-var))
389                 (overflow (cache-overflow ,cache-var))
390                 ,@wrapper-bindings)
391             (declare (fixnum size mask))
392             ,(emit-cache-lookup wrapper-vars miss-tag value-var)
393             ,hit-form))
394       ,miss-tag
395         (return ,miss-form))))
396
397 (defun emit-cache-lookup (wrapper-vars miss-tag value-reg)
398   (cond ((cdr wrapper-vars)
399          (emit-greater-than-1-dlap wrapper-vars miss-tag value-reg))
400         (value-reg
401          (emit-1-t-dlap (car wrapper-vars) miss-tag value-reg))
402         (t
403          (emit-1-nil-dlap (car wrapper-vars) miss-tag))))
404
405 (defun emit-1-nil-dlap (wrapper miss-label)
406   `(let* ((primary ,(emit-1-wrapper-compute-primary-cache-location wrapper
407                                                                    miss-label))
408           (location primary))
409      (declare (fixnum primary location))
410      (block search
411        (loop (when (eq ,wrapper (cache-vector-ref cache-vector location))
412                (return-from search nil))
413              (setq location (the fixnum (+ location 1)))
414              (when (= location size)
415                (setq location 0))
416              (when (= location primary)
417                (dolist (entry overflow)
418                  (when (eq (car entry) ,wrapper)
419                    (return-from search nil)))
420                (go ,miss-label))))))
421
422 (defmacro get-cache-vector-lock-count (cache-vector)
423   `(let ((lock-count (cache-vector-lock-count ,cache-vector)))
424      (unless (typep lock-count 'fixnum)
425        (error "My cache got freed somehow."))
426      (the fixnum lock-count)))
427
428 (defun emit-1-t-dlap (wrapper miss-label value)
429   `(let ((primary ,(emit-1-wrapper-compute-primary-cache-location wrapper
430                                                                   miss-label))
431          (initial-lock-count (get-cache-vector-lock-count cache-vector)))
432      (declare (fixnum primary initial-lock-count))
433      (let ((location primary))
434        (declare (fixnum location))
435        (block search
436          (loop (when (eq ,wrapper (cache-vector-ref cache-vector location))
437                  (setq ,value (cache-vector-ref cache-vector (1+ location)))
438                  (return-from search nil))
439                (setq location (the fixnum (+ location 2)))
440                (when (= location size)
441                  (setq location 0))
442                (when (= location primary)
443                  (dolist (entry overflow)
444                    (when (eq (car entry) ,wrapper)
445                      (setq ,value (cdr entry))
446                      (return-from search nil)))
447                  (go ,miss-label))))
448        (unless (= initial-lock-count
449                   (get-cache-vector-lock-count cache-vector))
450          (go ,miss-label)))))
451
452 (defun emit-greater-than-1-dlap (wrappers miss-label value)
453   (declare (type list wrappers))
454   (let ((cache-line-size (compute-line-size (+ (length wrappers)
455                                                (if value 1 0)))))
456     `(let ((primary 0)
457            (size-1 (the fixnum (- size 1))))
458        (declare (fixnum primary size-1))
459        ,(emit-n-wrapper-compute-primary-cache-location wrappers miss-label)
460        (let ((initial-lock-count (get-cache-vector-lock-count cache-vector)))
461          (declare (fixnum initial-lock-count))
462          (let ((location primary)
463                (next-location 0))
464            (declare (fixnum location next-location))
465            (block search
466              (loop (setq next-location
467                          (the fixnum (+ location ,cache-line-size)))
468                    (when (and ,@(mapcar
469                                  (lambda (wrapper)
470                                    `(eq ,wrapper
471                                         (cache-vector-ref
472                                          cache-vector
473                                          (setq location
474                                                (the fixnum (+ location 1))))))
475                                  wrappers))
476                      ,@(when value
477                          `((setq location (the fixnum (+ location 1)))
478                            (setq ,value (cache-vector-ref cache-vector
479                                                           location))))
480                      (return-from search nil))
481                    (setq location next-location)
482                    (when (= location size-1)
483                      (setq location 0))
484                    (when (= location primary)
485                      (dolist (entry overflow)
486                        (let ((entry-wrappers (car entry)))
487                          (when (and ,@(mapcar (lambda (wrapper)
488                                                 `(eq ,wrapper
489                                                      (pop entry-wrappers)))
490                                               wrappers))
491                            ,@(when value
492                                `((setq ,value (cdr entry))))
493                            (return-from search nil))))
494                      (go ,miss-label))))
495            (unless (= initial-lock-count
496                       (get-cache-vector-lock-count cache-vector))
497              (go ,miss-label)))))))
498
499 (defun emit-1-wrapper-compute-primary-cache-location (wrapper miss-label)
500   `(let ((wrapper-cache-no (layout-clos-hash ,wrapper)))
501      (declare (fixnum wrapper-cache-no))
502      (when (zerop wrapper-cache-no) (go ,miss-label))
503      ,(let ((form `(logand mask wrapper-cache-no)))
504         `(the fixnum ,form))))
505
506 (defun emit-n-wrapper-compute-primary-cache-location (wrappers miss-label)
507   (declare (type list wrappers))
508   ;; This returns 1 less that the actual location.
509   `(progn
510      ,@(let ((adds 0) (len (length wrappers)))
511          (declare (fixnum adds len))
512          (mapcar (lambda (wrapper)
513                    `(let ((wrapper-cache-no (layout-clos-hash ,wrapper)))
514                       (declare (fixnum wrapper-cache-no))
515                       (when (zerop wrapper-cache-no) (go ,miss-label))
516                       (setq primary (the fixnum (+ primary wrapper-cache-no)))
517                       ,@(progn
518                           (incf adds)
519                           (when (or (zerop (mod adds
520                                                 wrapper-cache-number-adds-ok))
521                                     (eql adds len))
522                             `((setq primary
523                                     ,(let ((form `(logand primary mask)))
524                                        `(the fixnum ,form))))))))
525                  wrappers))))
526
527 ;;; CMU17 (and SBCL) note: Since STD-INSTANCE-P is weakened in the
528 ;;; CMU/SBCL approach of using funcallable instances, that branch may
529 ;;; run on non-pcl instances (structures). The result will be the
530 ;;; non-wrapper layout for the structure, which will cause a miss. The
531 ;;; "slots" will be whatever the first slot is, but will be ignored.
532 ;;; Similarly, FSC-INSTANCE-P returns true on funcallable structures
533 ;;; as well as PCL fins.
534 (defun emit-fetch-wrapper (metatype argument miss-label &optional slot)
535   (ecase metatype
536     ((standard-instance)
537      `(cond ((std-instance-p ,argument)
538              ,@(when slot `((setq ,slot (std-instance-slots ,argument))))
539              (std-instance-wrapper ,argument))
540             ((fsc-instance-p ,argument)
541              ,@(when slot `((setq ,slot (fsc-instance-slots ,argument))))
542              (fsc-instance-wrapper ,argument))
543             (t
544              (go ,miss-label))))
545     ;; Sep92 PCL used to distinguish between some of these cases (and
546     ;; spuriously exclude others).  Since in SBCL
547     ;; WRAPPER-OF/LAYOUT-OF/BUILT-IN-OR-STRUCTURE-WRAPPER are all
548     ;; equivalent and inlined to each other, we can collapse some
549     ;; spurious differences.
550     ((class built-in-instance structure-instance condition-instance)
551      (when slot (error "can't do a slot reg for this metatype"))
552      `(wrapper-of ,argument))
553     ;; a metatype of NIL should never be seen here, as NIL is only in
554     ;; the metatypes before a generic function is fully initialized.
555     ;; T should never be seen because we never need to get a wrapper
556     ;; to do dispatch if all methods have T as the respective
557     ;; specializer.
558     ((t nil)
559      (bug "~@<metatype ~S seen in ~S.~@:>" metatype 'emit-fetch-wrapper))))