eeb865110e99eb70db773b398e59f5034c0b8c1d
[sbcl.git] / src / compiler / pack.lisp
1 ;;;; This file contains the implementation-independent code for Pack
2 ;;;; phase in the compiler. Pack is responsible for assigning TNs to
3 ;;;; storage allocations or "register allocation".
4
5 ;;;; This software is part of the SBCL system. See the README file for
6 ;;;; more information.
7 ;;;;
8 ;;;; This software is derived from the CMU CL system, which was
9 ;;;; written at Carnegie Mellon University and released into the
10 ;;;; public domain. The software is in the public domain and is
11 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
12 ;;;; files for more information.
13
14 (in-package "SB!C")
15
16 ;;; for debugging: some parameters controlling which optimizations we
17 ;;; attempt
18 (defvar *pack-assign-costs* t)
19 (defvar *pack-optimize-saves* t)
20 ;;; FIXME: Perhaps SB-FLUID should be renamed to SB-TWEAK and these
21 ;;; should be made conditional on SB-TWEAK.
22
23 (declaim (ftype (function (component) index) ir2-block-count))
24 \f
25 ;;;; conflict determination
26
27 ;;; Return true if the element at the specified offset in SB has a
28 ;;; conflict with TN:
29 ;;; -- If a component-live TN (:COMPONENT kind), then iterate over
30 ;;;    all the blocks. If the element at OFFSET is used anywhere in
31 ;;;    any of the component's blocks (always-live /= 0), then there
32 ;;;    is a conflict.
33 ;;; -- If TN is global (Confs true), then iterate over the blocks TN
34 ;;;    is live in (using TN-GLOBAL-CONFLICTS). If the TN is live
35 ;;;    everywhere in the block (:LIVE), then there is a conflict
36 ;;;    if the element at offset is used anywhere in the block
37 ;;;    (Always-Live /= 0). Otherwise, we use the local TN number for
38 ;;;    TN in block to find whether TN has a conflict at Offset in
39 ;;;    that block.
40 ;;; -- If TN is local, then we just check for a conflict in the block
41 ;;;    it is local to.
42 (defun offset-conflicts-in-sb (tn sb offset)
43   (declare (type tn tn) (type finite-sb sb) (type index offset))
44   (let ((confs (tn-global-conflicts tn))
45         (kind (tn-kind tn)))
46     (cond
47      ((eq kind :component)
48       (let ((loc-live (svref (finite-sb-always-live sb) offset)))
49         (dotimes (i (ir2-block-count *component-being-compiled*) nil)
50           (when (/= (sbit loc-live i) 0)
51             (return t)))))
52      (confs
53       (let ((loc-confs (svref (finite-sb-conflicts sb) offset))
54             (loc-live (svref (finite-sb-always-live sb) offset)))
55         (do ((conf confs (global-conflicts-next-tnwise conf)))
56             ((null conf)
57              nil)
58           (let* ((block (global-conflicts-block conf))
59                  (num (ir2-block-number block)))
60             (if (eq (global-conflicts-kind conf) :live)
61                 (when (/= (sbit loc-live num) 0)
62                   (return t))
63                 (when (/= (sbit (svref loc-confs num)
64                                 (global-conflicts-number conf))
65                           0)
66                   (return t)))))))
67      (t
68       (/= (sbit (svref (svref (finite-sb-conflicts sb) offset)
69                        (ir2-block-number (tn-local tn)))
70                 (tn-local-number tn))
71           0)))))
72
73 ;;; Return true if TN has a conflict in SC at the specified offset.
74 (defun conflicts-in-sc (tn sc offset)
75   (declare (type tn tn) (type sc sc) (type index offset))
76   (let ((sb (sc-sb sc)))
77     (dotimes (i (sc-element-size sc) nil)
78       (when (offset-conflicts-in-sb tn sb (+ offset i))
79         (return t)))))
80
81 ;;; Add TN's conflicts into the conflicts for the location at OFFSET
82 ;;; in SC. We iterate over each location in TN, adding to the
83 ;;; conflicts for that location:
84 ;;; -- If TN is a :COMPONENT TN, then iterate over all the blocks,
85 ;;;    setting all of the local conflict bits and the always-live bit.
86 ;;;    This records a conflict with any TN that has a LTN number in
87 ;;;    the block, as well as with :ALWAYS-LIVE and :ENVIRONMENT TNs.
88 ;;; -- If TN is global, then iterate over the blocks TN is live in. In
89 ;;;    addition to setting the always-live bit to represent the conflict
90 ;;;    with TNs live throughout the block, we also set bits in the
91 ;;;    local conflicts. If TN is :ALWAYS-LIVE in the block, we set all
92 ;;;    the bits, otherwise we OR in the local conflict bits.
93 ;;; -- If the TN is local, then we just do the block it is local to,
94 ;;;    setting always-live and OR'ing in the local conflicts.
95 (defun add-location-conflicts (tn sc offset optimize)
96   (declare (type tn tn) (type sc sc) (type index offset))
97   (let ((confs (tn-global-conflicts tn))
98         (sb (sc-sb sc))
99         (kind (tn-kind tn)))
100     (dotimes (i (sc-element-size sc))
101       (declare (type index i))
102       (let* ((this-offset (+ offset i))
103              (loc-confs (svref (finite-sb-conflicts sb) this-offset))
104              (loc-live (svref (finite-sb-always-live sb) this-offset)))
105         (cond
106          ((eq kind :component)
107           (dotimes (num (ir2-block-count *component-being-compiled*))
108             (declare (type index num))
109             (setf (sbit loc-live num) 1)
110             (set-bit-vector (svref loc-confs num))))
111          (confs
112           (do ((conf confs (global-conflicts-next-tnwise conf)))
113               ((null conf))
114             (let* ((block (global-conflicts-block conf))
115                    (num (ir2-block-number block))
116                    (local-confs (svref loc-confs num)))
117               (declare (type local-tn-bit-vector local-confs))
118               (setf (sbit loc-live num) 1)
119               (if (eq (global-conflicts-kind conf) :live)
120                   (set-bit-vector local-confs)
121                   (bit-ior local-confs (global-conflicts-conflicts conf) t)))))
122          (t
123           (let ((num (ir2-block-number (tn-local tn))))
124             (setf (sbit loc-live num) 1)
125             (bit-ior (the local-tn-bit-vector (svref loc-confs num))
126                      (tn-local-conflicts tn) t))))
127         ;; Calculating ALWAYS-LIVE-COUNT is moderately expensive, and
128         ;; currently the information isn't used unless (> SPEED
129         ;; COMPILE-SPEED).
130         (when optimize
131           (setf (svref (finite-sb-always-live-count sb) this-offset)
132                 (find-location-usage sb this-offset))))))
133   (values))
134
135 ;; A rought measure of how much a given OFFSET in SB is currently
136 ;; used. Current implementation counts the amount of blocks where the
137 ;; offset has been marked as ALWAYS-LIVE.
138 (defun find-location-usage (sb offset)
139   (declare (optimize speed))
140   (declare (type sb sb) (type index offset))
141   (let* ((always-live (svref (finite-sb-always-live sb) offset)))
142     (declare (simple-bit-vector always-live))
143     (count 1 always-live)))
144
145 ;;; Return the total number of IR2-BLOCKs in COMPONENT.
146 (defun ir2-block-count (component)
147   (declare (type component component))
148   (do ((2block (block-info (block-next (component-head component)))
149                (ir2-block-next 2block)))
150       ((null 2block)
151        (error "What?  No ir2 blocks have a non-nil number?"))
152     (when (ir2-block-number 2block)
153       (return (1+ (ir2-block-number 2block))))))
154
155 ;;; Ensure that the conflicts vectors for each :FINITE SB are large
156 ;;; enough for the number of blocks allocated. Also clear any old
157 ;;; conflicts and reset the current size to the initial size.
158 (defun init-sb-vectors (component)
159   (let ((nblocks (ir2-block-count component)))
160     (dolist (sb *backend-sb-list*)
161       (unless (eq (sb-kind sb) :non-packed)
162         (let* ((conflicts (finite-sb-conflicts sb))
163                (always-live (finite-sb-always-live sb))
164                (always-live-count (finite-sb-always-live-count sb))
165                (max-locs (length conflicts))
166                (last-count (finite-sb-last-block-count sb)))
167           (unless (zerop max-locs)
168             (let ((current-size (length (the simple-vector
169                                              (svref conflicts 0)))))
170               (cond
171                ((> nblocks current-size)
172                 (let ((new-size (max nblocks (* current-size 2))))
173                   (declare (type index new-size))
174                   (dotimes (i max-locs)
175                     (declare (type index i))
176                     (let ((new-vec (make-array new-size)))
177                       (let ((old (svref conflicts i)))
178                         (declare (simple-vector old))
179                         (dotimes (j current-size)
180                           (declare (type index j))
181                           (setf (svref new-vec j)
182                                 (clear-bit-vector (svref old j)))))
183
184                       (do ((j current-size (1+ j)))
185                           ((= j new-size))
186                         (declare (type index j))
187                         (setf (svref new-vec j)
188                               (make-array local-tn-limit :element-type 'bit
189                                           :initial-element 0)))
190                       (setf (svref conflicts i) new-vec))
191                     (setf (svref always-live i)
192                           (make-array new-size :element-type 'bit
193                                       :initial-element 0))
194                     (setf (svref always-live-count i) 0))))
195                (t
196                 (dotimes (i (finite-sb-current-size sb))
197                   (declare (type index i))
198                   (let ((conf (svref conflicts i)))
199                     (declare (simple-vector conf))
200                     (dotimes (j last-count)
201                       (declare (type index j))
202                       (clear-bit-vector (svref conf j))))
203                   (clear-bit-vector (svref always-live i))
204                   (setf (svref always-live-count i) 0))))))
205
206           (setf (finite-sb-last-block-count sb) nblocks)
207           (setf (finite-sb-current-size sb) (sb-size sb))
208           (setf (finite-sb-last-offset sb) 0))))))
209
210 ;;; Expand the :UNBOUNDED SB backing SC by either the initial size or
211 ;;; the SC element size, whichever is larger. If NEEDED-SIZE is
212 ;;; larger, then use that size.
213 (defun grow-sc (sc &optional (needed-size 0))
214   (declare (type sc sc) (type index needed-size))
215   (let* ((sb (sc-sb sc))
216          (size (finite-sb-current-size sb))
217          (align-mask (1- (sc-alignment sc)))
218          (inc (max (finite-sb-size-increment sb)
219                    (+ (sc-element-size sc)
220                       (- (logandc2 (+ size align-mask) align-mask)
221                          size))
222                    (- needed-size size)))
223          (new-size (let ((align-mask (1- (finite-sb-size-alignment sb))))
224                      (logandc2 (+  size inc align-mask) align-mask)))
225          (conflicts (finite-sb-conflicts sb))
226          (block-size (if (zerop (length conflicts))
227                          (ir2-block-count *component-being-compiled*)
228                          (length (the simple-vector (svref conflicts 0))))))
229     (declare (type index inc new-size))
230     (aver (eq (sb-kind sb) :unbounded))
231
232     (when (> new-size (length conflicts))
233       (let ((new-conf (make-array new-size)))
234         (replace new-conf conflicts)
235         (do ((i size (1+ i)))
236             ((= i new-size))
237           (declare (type index i))
238           (let ((loc-confs (make-array block-size)))
239             (dotimes (j block-size)
240               (setf (svref loc-confs j)
241                     (make-array local-tn-limit
242                                 :initial-element 0
243                                 :element-type 'bit)))
244             (setf (svref new-conf i) loc-confs)))
245         (setf (finite-sb-conflicts sb) new-conf))
246
247       (let ((new-live (make-array new-size)))
248         (replace new-live (finite-sb-always-live sb))
249         (do ((i size (1+ i)))
250             ((= i new-size))
251           (setf (svref new-live i)
252                 (make-array block-size
253                             :initial-element 0
254                             :element-type 'bit)))
255         (setf (finite-sb-always-live sb) new-live))
256
257       (let ((new-live-count (make-array new-size)))
258         (declare (optimize speed)) ;; FILL deftransform
259         (replace new-live-count (finite-sb-always-live-count sb))
260         (fill new-live-count 0 :start size)
261         (setf (finite-sb-always-live-count sb) new-live-count))
262
263       (let ((new-tns (make-array new-size :initial-element nil)))
264         (replace new-tns (finite-sb-live-tns sb))
265         (fill (finite-sb-live-tns sb) nil)
266         (setf (finite-sb-live-tns sb) new-tns)))
267
268     (setf (finite-sb-current-size sb) new-size))
269   (values))
270
271 \f
272 ;;;; internal errors
273
274 ;;; Give someone a hard time because there isn't any load function
275 ;;; defined to move from SRC to DEST.
276 (defun no-load-fun-error (src dest)
277   (let* ((src-sc (tn-sc src))
278          (src-name (sc-name src-sc))
279          (dest-sc (tn-sc dest))
280          (dest-name (sc-name dest-sc)))
281     (cond ((eq (sb-kind (sc-sb src-sc)) :non-packed)
282            (unless (member src-sc (sc-constant-scs dest-sc))
283              (error "loading from an invalid constant SC?~@
284                      VM definition inconsistent, try recompiling."))
285            (error "no load function defined to load SC ~S ~
286                    from its constant SC ~S"
287                   dest-name src-name))
288           ((member src-sc (sc-alternate-scs dest-sc))
289            (error "no load function defined to load SC ~S from its ~
290                    alternate SC ~S"
291                   dest-name src-name))
292           ((member dest-sc (sc-alternate-scs src-sc))
293            (error "no load function defined to save SC ~S in its ~
294                    alternate SC ~S"
295                   src-name dest-name))
296           (t
297            ;; FIXME: "VM definition is inconsistent" shouldn't be a
298            ;; possibility in SBCL.
299            (error "loading to/from SCs that aren't alternates?~@
300                    VM definition is inconsistent, try recompiling.")))))
301
302 ;;; Called when we failed to pack TN. If RESTRICTED is true, then we
303 ;;; are restricted to pack TN in its SC.
304 (defun failed-to-pack-error (tn restricted)
305   (declare (type tn tn))
306   (let* ((sc (tn-sc tn))
307          (scs (cons sc (sc-alternate-scs sc))))
308     (cond
309      (restricted
310       (error "failed to pack restricted TN ~S in its SC ~S"
311              tn (sc-name sc)))
312      (t
313       (aver (not (find :unbounded scs
314                        :key (lambda (x) (sb-kind (sc-sb x))))))
315       (let ((ptype (tn-primitive-type tn)))
316         (cond
317          (ptype
318           (aver (member (sc-number sc) (primitive-type-scs ptype)))
319           (error "SC ~S doesn't have any :UNBOUNDED alternate SCs, but is~@
320                   a SC for primitive-type ~S."
321                  (sc-name sc) (primitive-type-name ptype)))
322          (t
323           (error "SC ~S doesn't have any :UNBOUNDED alternate SCs."
324                  (sc-name sc)))))))))
325
326 ;;; Return a list of format arguments describing how TN is used in
327 ;;; OP's VOP.
328 (defun describe-tn-use (loc tn op)
329   (let* ((vop (tn-ref-vop op))
330          (args (vop-args vop))
331          (results (vop-results vop))
332          (name (with-output-to-string (stream)
333                  (print-tn-guts tn stream)))
334          (2comp (component-info *component-being-compiled*))
335          temp)
336     (cond
337      ((setq temp (position-in #'tn-ref-across tn args :key #'tn-ref-tn))
338       `("~2D: ~A (~:R argument)" ,loc ,name ,(1+ temp)))
339      ((setq temp (position-in #'tn-ref-across tn results :key #'tn-ref-tn))
340       `("~2D: ~A (~:R result)" ,loc ,name ,(1+ temp)))
341      ((setq temp (position-in #'tn-ref-across tn args :key #'tn-ref-load-tn))
342       `("~2D: ~A (~:R argument load TN)" ,loc ,name ,(1+ temp)))
343      ((setq temp (position-in #'tn-ref-across tn results :key
344                               #'tn-ref-load-tn))
345       `("~2D: ~A (~:R result load TN)" ,loc ,name ,(1+ temp)))
346      ((setq temp (position-in #'tn-ref-across tn (vop-temps vop)
347                               :key #'tn-ref-tn))
348       `("~2D: ~A (temporary ~A)" ,loc ,name
349         ,(operand-parse-name (elt (vop-parse-temps
350                                    (vop-parse-or-lose
351                                     (vop-info-name  (vop-info vop))))
352                                   temp))))
353      ((eq (tn-kind tn) :component)
354       `("~2D: ~A (component live)" ,loc ,name))
355      ((position-in #'tn-next tn (ir2-component-wired-tns 2comp))
356       `("~2D: ~A (wired)" ,loc ,name))
357      ((position-in #'tn-next tn (ir2-component-restricted-tns 2comp))
358       `("~2D: ~A (restricted)" ,loc ,name))
359      (t
360       `("~2D: not referenced?" ,loc)))))
361
362 ;;; If load TN packing fails, try to give a helpful error message. We
363 ;;; find a TN in each location that conflicts, and print it.
364 (defun failed-to-pack-load-tn-error (scs op)
365   (declare (list scs) (type tn-ref op))
366   (collect ((used)
367             (unused))
368     (dolist (sc scs)
369       (let* ((sb (sc-sb sc))
370              (confs (finite-sb-live-tns sb)))
371         (aver (eq (sb-kind sb) :finite))
372         (dolist (el (sc-locations sc))
373           (declare (type index el))
374           (let ((conf (load-tn-conflicts-in-sc op sc el t)))
375             (if conf
376                 (used (describe-tn-use el conf op))
377                 (do ((i el (1+ i))
378                      (end (+ el (sc-element-size sc))))
379                     ((= i end)
380                      (unused el))
381                   (declare (type index i end))
382                   (let ((victim (svref confs i)))
383                     (when victim
384                       (used (describe-tn-use el victim op))
385                       (return t)))))))))
386
387     (multiple-value-bind (arg-p n more-p costs load-scs incon)
388         (get-operand-info op)
389       (declare (ignore costs load-scs))
390         (aver (not more-p))
391         (error "unable to pack a Load-TN in SC ~{~A~#[~^~;, or ~:;,~]~} ~
392                 for the ~:R ~:[result~;argument~] to~@
393                 the ~S VOP,~@
394                 ~:[since all SC elements are in use:~:{~%~@?~}~%~;~
395                 ~:*but these SC elements are not in use:~%  ~S~%Bug?~*~]~
396                 ~:[~;~@
397                 Current cost info inconsistent with that in effect at compile ~
398                 time. Recompile.~%Compilation order may be incorrect.~]"
399                (mapcar #'sc-name scs)
400                n arg-p
401                (vop-info-name (vop-info (tn-ref-vop op)))
402                (unused) (used)
403                incon))))
404
405 ;;; This is called when none of the SCs that we can load OP into are
406 ;;; allowed by OP's primitive-type.
407 (defun no-load-scs-allowed-by-primitive-type-error (ref)
408   (declare (type tn-ref ref))
409   (let* ((tn (tn-ref-tn ref))
410          (ptype (tn-primitive-type tn)))
411     (multiple-value-bind (arg-p pos more-p costs load-scs incon)
412         (get-operand-info ref)
413       (declare (ignore costs))
414       (aver (not more-p))
415       (error "~S is not valid as the ~:R ~:[result~;argument~] to VOP:~
416               ~%  ~S,~@
417               since the TN's primitive type ~S doesn't allow any of the SCs~@
418               allowed by the operand restriction:~%  ~S~
419               ~:[~;~@
420               Current cost info inconsistent with that in effect at compile ~
421               time. Recompile.~%Compilation order may be incorrect.~]"
422              tn pos arg-p
423              (template-name (vop-info (tn-ref-vop ref)))
424              (primitive-type-name ptype)
425              (mapcar #'sc-name (listify-restrictions load-scs))
426              incon))))
427 \f
428 ;;;; register saving
429
430 ;;; Do stuff to note that TN is spilled at VOP for the debugger's benefit.
431 (defun note-spilled-tn (tn vop)
432   (when (and (tn-leaf tn) (vop-save-set vop))
433     (let ((2comp (component-info *component-being-compiled*)))
434       (setf (gethash tn (ir2-component-spilled-tns 2comp)) t)
435       (pushnew tn (gethash vop (ir2-component-spilled-vops 2comp)))))
436   (values))
437
438 ;;; Make a save TN for TN, pack it, and return it. We copy various
439 ;;; conflict information from the TN so that pack does the right
440 ;;; thing.
441 (defun pack-save-tn (tn)
442   (declare (type tn tn))
443   (let ((res (make-tn 0 :save nil nil)))
444     (dolist (alt (sc-alternate-scs (tn-sc tn))
445                  (error "no unbounded alternate for SC ~S"
446                         (sc-name (tn-sc tn))))
447       (when (eq (sb-kind (sc-sb alt)) :unbounded)
448         (setf (tn-save-tn tn) res)
449         (setf (tn-save-tn res) tn)
450         (setf (tn-sc res) alt)
451         (pack-tn res t nil)
452         (return res)))))
453
454 ;;; Find the load function for moving from SRC to DEST and emit a
455 ;;; MOVE-OPERAND VOP with that function as its info arg.
456 (defun emit-operand-load (node block src dest before)
457   (declare (type node node) (type ir2-block block)
458            (type tn src dest) (type (or vop null) before))
459   (emit-load-template node block
460                       (template-or-lose 'move-operand)
461                       src dest
462                       (list (or (svref (sc-move-funs (tn-sc dest))
463                                        (sc-number (tn-sc src)))
464                                 (no-load-fun-error src dest)))
465                       before)
466   (values))
467
468 ;;; Find the preceding use of the VOP NAME in the emit order, starting
469 ;;; with VOP. We must find the VOP in the same IR1 block.
470 (defun reverse-find-vop (name vop)
471   (do* ((block (vop-block vop) (ir2-block-prev block))
472         (last vop (ir2-block-last-vop block)))
473        (nil)
474     (aver (eq (ir2-block-block block) (ir2-block-block (vop-block vop))))
475     (do ((current last (vop-prev current)))
476         ((null current))
477       (when (eq (vop-info-name (vop-info current)) name)
478         (return-from reverse-find-vop current)))))
479
480 ;;; For TNs that have other than one writer, we save the TN before
481 ;;; each call. If a local call (MOVE-ARGS is :LOCAL-CALL), then we
482 ;;; scan back for the ALLOCATE-FRAME VOP, and emit the save there.
483 ;;; This is necessary because in a self-recursive local call, the
484 ;;; registers holding the current arguments may get trashed by setting
485 ;;; up the call arguments. The ALLOCATE-FRAME VOP marks a place at
486 ;;; which the values are known to be good.
487 (defun save-complex-writer-tn (tn vop)
488   (let ((save (or (tn-save-tn tn)
489                   (pack-save-tn tn)))
490         (node (vop-node vop))
491         (block (vop-block vop))
492         (next (vop-next vop)))
493     (when (eq (tn-kind save) :specified-save)
494       (setf (tn-kind save) :save))
495     (aver (eq (tn-kind save) :save))
496     (emit-operand-load node block tn save
497                        (if (eq (vop-info-move-args (vop-info vop))
498                                :local-call)
499                            (reverse-find-vop 'allocate-frame vop)
500                            vop))
501     (emit-operand-load node block save tn next)))
502
503 ;;; Return a VOP after which is an OK place to save the value of TN.
504 ;;; For correctness, it is only required that this location be after
505 ;;; any possible write and before any possible restore location.
506 ;;;
507 ;;; In practice, we return the unique writer VOP, but give up if the
508 ;;; TN is ever read by a VOP with MOVE-ARGS :LOCAL-CALL. This prevents
509 ;;; us from being confused by non-tail local calls.
510 ;;;
511 ;;; When looking for writes, we have to ignore uses of MOVE-OPERAND,
512 ;;; since they will correspond to restores that we have already done.
513 (defun find-single-writer (tn)
514   (declare (type tn tn))
515   (do ((write (tn-writes tn) (tn-ref-next write))
516        (res nil))
517       ((null write)
518        (when (and res
519                   (do ((read (tn-reads tn) (tn-ref-next read)))
520                       ((not read) t)
521                     (when (eq (vop-info-move-args
522                                (vop-info
523                                 (tn-ref-vop read)))
524                               :local-call)
525                       (return nil))))
526          (tn-ref-vop res)))
527
528     (unless (eq (vop-info-name (vop-info (tn-ref-vop write)))
529                 'move-operand)
530       (when res (return nil))
531       (setq res write))))
532
533 ;;; Try to save TN at a single location. If we succeed, return T,
534 ;;; otherwise NIL.
535 (defun save-single-writer-tn (tn)
536   (declare (type tn tn))
537   (let* ((old-save (tn-save-tn tn))
538          (save (or old-save (pack-save-tn tn)))
539          (writer (find-single-writer tn)))
540     (when (and writer
541                (or (not old-save)
542                    (eq (tn-kind old-save) :specified-save)))
543       (emit-operand-load (vop-node writer) (vop-block writer)
544                          tn save (vop-next writer))
545       (setf (tn-kind save) :save-once)
546       t)))
547
548 ;;; Restore a TN with a :SAVE-ONCE save TN.
549 (defun restore-single-writer-tn (tn vop)
550   (declare (type tn) (type vop vop))
551   (let ((save (tn-save-tn tn)))
552     (aver (eq (tn-kind save) :save-once))
553     (emit-operand-load (vop-node vop) (vop-block vop) save tn (vop-next vop)))
554   (values))
555
556 ;;; Save a single TN that needs to be saved, choosing save-once if
557 ;;; appropriate. This is also called by SPILL-AND-PACK-LOAD-TN.
558 (defun basic-save-tn (tn vop)
559   (declare (type tn tn) (type vop vop))
560   (let ((save (tn-save-tn tn)))
561     (cond ((and save (eq (tn-kind save) :save-once))
562            (restore-single-writer-tn tn vop))
563           ((save-single-writer-tn tn)
564            (restore-single-writer-tn tn vop))
565           (t
566            (save-complex-writer-tn tn vop))))
567   (values))
568
569 ;;; Scan over the VOPs in BLOCK, emiting saving code for TNs noted in
570 ;;; the codegen info that are packed into saved SCs.
571 (defun emit-saves (block)
572   (declare (type ir2-block block))
573   (do ((vop (ir2-block-start-vop block) (vop-next vop)))
574       ((null vop))
575     (when (eq (vop-info-save-p (vop-info vop)) t)
576       (do-live-tns (tn (vop-save-set vop) block)
577         (when (and (sc-save-p (tn-sc tn))
578                    (not (eq (tn-kind tn) :component)))
579           (basic-save-tn tn vop)))))
580
581   (values))
582 \f
583 ;;;; optimized saving
584
585 ;;; Save TN if it isn't a single-writer TN that has already been
586 ;;; saved. If multi-write, we insert the save BEFORE the specified
587 ;;; VOP. CONTEXT is a VOP used to tell which node/block to use for the
588 ;;; new VOP.
589 (defun save-if-necessary (tn before context)
590   (declare (type tn tn) (type (or vop null) before) (type vop context))
591   (let ((save (tn-save-tn tn)))
592     (when (eq (tn-kind save) :specified-save)
593       (setf (tn-kind save) :save))
594     (aver (member (tn-kind save) '(:save :save-once)))
595     (unless (eq (tn-kind save) :save-once)
596       (or (save-single-writer-tn tn)
597           (emit-operand-load (vop-node context) (vop-block context)
598                              tn save before))))
599   (values))
600
601 ;;; Load the TN from its save location, allocating one if necessary.
602 ;;; The load is inserted BEFORE the specified VOP. CONTEXT is a VOP
603 ;;; used to tell which node/block to use for the new VOP.
604 (defun restore-tn (tn before context)
605   (declare (type tn tn) (type (or vop null) before) (type vop context))
606   (let ((save (or (tn-save-tn tn) (pack-save-tn tn))))
607     (emit-operand-load (vop-node context) (vop-block context)
608                        save tn before))
609   (values))
610
611 ;;; Start scanning backward at the end of BLOCK, looking which TNs are
612 ;;; live and looking for places where we have to save. We manipulate
613 ;;; two sets: SAVES and RESTORES.
614 ;;;
615 ;;; SAVES is a set of all the TNs that have to be saved because they
616 ;;; are restored after some call. We normally delay saving until the
617 ;;; beginning of the block, but we must save immediately if we see a
618 ;;; write of the saved TN. We also immediately save all TNs and exit
619 ;;; when we see a NOTE-ENVIRONMENT-START VOP, since saves can't be
620 ;;; done before the environment is properly initialized.
621 ;;;
622 ;;; RESTORES is a set of all the TNs read (and not written) between
623 ;;; here and the next call, i.e. the set of TNs that must be restored
624 ;;; when we reach the next (earlier) call VOP. Unlike SAVES, this set
625 ;;; is cleared when we do the restoring after a call. Any TNs that
626 ;;; were in RESTORES are moved into SAVES to ensure that they are
627 ;;; saved at some point.
628 ;;;
629 ;;; SAVES and RESTORES are represented using both a list and a
630 ;;; bit-vector so that we can quickly iterate and test for membership.
631 ;;; The incoming SAVES and RESTORES args are used for computing these
632 ;;; sets (the initial contents are ignored.)
633 ;;;
634 ;;; When we hit a VOP with :COMPUTE-ONLY SAVE-P (an internal error
635 ;;; location), we pretend that all live TNs were read, unless (= speed
636 ;;; 3), in which case we mark all the TNs that are live but not
637 ;;; restored as spilled.
638 (defun optimized-emit-saves-block (block saves restores)
639   (declare (type ir2-block block) (type simple-bit-vector saves restores))
640   (let ((1block (ir2-block-block block))
641         (saves-list ())
642         (restores-list ())
643         (skipping nil))
644     (declare (list saves-list restores-list))
645     (clear-bit-vector saves)
646     (clear-bit-vector restores)
647     (do-live-tns (tn (ir2-block-live-in block) block)
648       (when (and (sc-save-p (tn-sc tn))
649                  (not (eq (tn-kind tn) :component)))
650         (let ((num (tn-number tn)))
651           (setf (sbit restores num) 1)
652           (push tn restores-list))))
653
654     (do ((block block (ir2-block-prev block))
655          (prev nil block))
656         ((not (eq (ir2-block-block block) 1block))
657          (aver (not skipping))
658          (dolist (save saves-list)
659            (let ((start (ir2-block-start-vop prev)))
660              (save-if-necessary save start start)))
661          prev)
662       (do ((vop (ir2-block-last-vop block) (vop-prev vop)))
663           ((null vop))
664         (let ((info (vop-info vop)))
665           (case (vop-info-name info)
666             (allocate-frame
667              (aver skipping)
668              (setq skipping nil))
669             (note-environment-start
670              (aver (not skipping))
671              (dolist (save saves-list)
672                (save-if-necessary save (vop-next vop) vop))
673              (return-from optimized-emit-saves-block block)))
674
675           (unless skipping
676             (do ((write (vop-results vop) (tn-ref-across write)))
677                 ((null write))
678               (let* ((tn (tn-ref-tn write))
679                      (num (tn-number tn)))
680                 (unless (zerop (sbit restores num))
681                   (setf (sbit restores num) 0)
682                   (setq restores-list
683                         (delete tn restores-list :test #'eq)))
684                 (unless (zerop (sbit saves num))
685                   (setf (sbit saves num) 0)
686                   (save-if-necessary tn (vop-next vop) vop)
687                   (setq saves-list
688                         (delete tn saves-list :test #'eq))))))
689
690           (macrolet ((save-note-read (tn)
691                        `(let* ((tn ,tn)
692                                (num (tn-number tn)))
693                           (when (and (sc-save-p (tn-sc tn))
694                                      (zerop (sbit restores num))
695                                      (not (eq (tn-kind tn) :component)))
696                           (setf (sbit restores num) 1)
697                           (push tn restores-list)))))
698
699             (case (vop-info-save-p info)
700               ((t)
701                (dolist (tn restores-list)
702                  (restore-tn tn (vop-next vop) vop)
703                  (let ((num (tn-number tn)))
704                    (when (zerop (sbit saves num))
705                      (push tn saves-list)
706                      (setf (sbit saves num) 1))))
707                (setq restores-list nil)
708                (clear-bit-vector restores))
709               (:compute-only
710                (cond ((policy (vop-node vop) (= speed 3))
711                       (do-live-tns (tn (vop-save-set vop) block)
712                         (when (zerop (sbit restores (tn-number tn)))
713                           (note-spilled-tn tn vop))))
714                      (t
715                       (do-live-tns (tn (vop-save-set vop) block)
716                         (save-note-read tn))))))
717
718             (if (eq (vop-info-move-args info) :local-call)
719                 (setq skipping t)
720                 (do ((read (vop-args vop) (tn-ref-across read)))
721                     ((null read))
722                   (save-note-read (tn-ref-tn read))))))))))
723
724 ;;; This is like EMIT-SAVES, only different. We avoid redundant saving
725 ;;; within the block, and don't restore values that aren't used before
726 ;;; the next call. This function is just the top level loop over the
727 ;;; blocks in the component, which locates blocks that need saving
728 ;;; done.
729 (defun optimized-emit-saves (component)
730   (declare (type component component))
731   (let* ((gtn-count (1+ (ir2-component-global-tn-counter
732                          (component-info component))))
733          (saves (make-array gtn-count :element-type 'bit))
734          (restores (make-array gtn-count :element-type 'bit))
735          (block (ir2-block-prev (block-info (component-tail component))))
736          (head (block-info (component-head component))))
737     (loop
738       (when (eq block head) (return))
739       (when (do ((vop (ir2-block-start-vop block) (vop-next vop)))
740                 ((null vop) nil)
741               (when (eq (vop-info-save-p (vop-info vop)) t)
742                 (return t)))
743         (setq block (optimized-emit-saves-block block saves restores)))
744       (setq block (ir2-block-prev block)))))
745
746 ;;; Iterate over the normal TNs, finding the cost of packing on the
747 ;;; stack in units of the number of references. We count all
748 ;;; references as +1, and subtract out REGISTER-SAVE-PENALTY for each
749 ;;; place where we would have to save a register.
750 (defun assign-tn-costs (component)
751   (do-ir2-blocks (block component)
752     (do ((vop (ir2-block-start-vop block) (vop-next vop)))
753         ((null vop))
754       (when (eq (vop-info-save-p (vop-info vop)) t)
755         (do-live-tns (tn (vop-save-set vop) block)
756           (decf (tn-cost tn) *backend-register-save-penalty*)))))
757
758   (do ((tn (ir2-component-normal-tns (component-info component))
759            (tn-next tn)))
760       ((null tn))
761     (let ((cost (tn-cost tn)))
762       (declare (fixnum cost))
763       (do ((ref (tn-reads tn) (tn-ref-next ref)))
764           ((null ref))
765         (incf cost))
766       (do ((ref (tn-writes tn) (tn-ref-next ref)))
767           ((null ref))
768         (incf cost))
769       (setf (tn-cost tn) cost))))
770
771 ;;; Iterate over the normal TNs, storing the depth of the deepest loop
772 ;;; that the TN is used in TN-LOOP-DEPTH.
773 (defun assign-tn-depths (component)
774   (when *loop-analyze*
775     (do-ir2-blocks (block component)
776       (do ((vop (ir2-block-start-vop block)
777                 (vop-next vop)))
778           ((null vop))
779         (flet ((find-all-tns (head-fun)
780                  (collect ((tns))
781                    (do ((ref (funcall head-fun vop) (tn-ref-across ref)))
782                        ((null ref))
783                      (tns (tn-ref-tn ref)))
784                    (tns))))
785           (dolist (tn (nconc (find-all-tns #'vop-args)
786                              (find-all-tns #'vop-results)
787                              (find-all-tns #'vop-temps)
788                              ;; What does "references in this VOP
789                              ;; mean"? Probably something that isn't
790                              ;; useful in this context, since these
791                              ;; TN-REFs are linked with TN-REF-NEXT
792                              ;; instead of TN-REF-ACROSS. --JES
793                              ;; 2004-09-11
794                              ;; (find-all-tns #'vop-refs)
795                              ))
796             (setf (tn-loop-depth tn)
797                   (max (tn-loop-depth tn)
798                        (let* ((ir1-block (ir2-block-block (vop-block vop)))
799                               (loop (block-loop ir1-block)))
800                          (if loop
801                              (loop-depth loop)
802                              0))))))))))
803
804 \f
805 ;;;; load TN packing
806
807 ;;; These variables indicate the last location at which we computed
808 ;;; the Live-TNs. They hold the BLOCK and VOP values that were passed
809 ;;; to COMPUTE-LIVE-TNS.
810 (defvar *live-block*)
811 (defvar *live-vop*)
812
813 ;;; If we unpack some TNs, then we mark all affected blocks by
814 ;;; sticking them in this hash-table. This is initially null. We
815 ;;; create the hashtable if we do any unpacking.
816 (defvar *repack-blocks*)
817 (declaim (type list *repack-blocks*))
818
819 ;;; Set the LIVE-TNS vectors in all :FINITE SBs to represent the TNs
820 ;;; live at the end of BLOCK.
821 (defun init-live-tns (block)
822   (dolist (sb *backend-sb-list*)
823     (when (eq (sb-kind sb) :finite)
824       (fill (finite-sb-live-tns sb) nil)))
825
826   (do-live-tns (tn (ir2-block-live-in block) block)
827     (let* ((sc (tn-sc tn))
828            (sb (sc-sb sc)))
829       (when (eq (sb-kind sb) :finite)
830         ;; KLUDGE: we can have "live" TNs that are neither read
831         ;; to nor written from, due to more aggressive (type-
832         ;; directed) constant propagation.  Such TNs will never
833         ;; be assigned an offset nor be in conflict with anything.
834         ;;
835         ;; Ideally, it seems to me we could make sure these TNs
836         ;; are never allocated in the first place in
837         ;; ASSIGN-LAMBDA-VAR-TNS.
838         (if (tn-offset tn)
839             (do ((offset (tn-offset tn) (1+ offset))
840                  (end (+ (tn-offset tn) (sc-element-size sc))))
841                 ((= offset end))
842               (declare (type index offset end))
843               (setf (svref (finite-sb-live-tns sb) offset) tn))
844             (assert (and (null (tn-reads tn))
845                          (null (tn-writes tn))))))))
846
847   (setq *live-block* block)
848   (setq *live-vop* (ir2-block-last-vop block))
849
850   (values))
851
852 ;;; Set the LIVE-TNs in :FINITE SBs to represent the TNs live
853 ;;; immediately after the evaluation of VOP in BLOCK, excluding
854 ;;; results of the VOP. If VOP is null, then compute the live TNs at
855 ;;; the beginning of the block. Sequential calls on the same block
856 ;;; must be in reverse VOP order.
857 (defun compute-live-tns (block vop)
858   (declare (type ir2-block block) (type vop vop))
859   (unless (eq block *live-block*)
860     (init-live-tns block))
861
862   (do ((current *live-vop* (vop-prev current)))
863       ((eq current vop)
864        (do ((res (vop-results vop) (tn-ref-across res)))
865            ((null res))
866          (let* ((tn (tn-ref-tn res))
867                 (sc (tn-sc tn))
868                 (sb (sc-sb sc)))
869            (when (eq (sb-kind sb) :finite)
870              (do ((offset (tn-offset tn) (1+ offset))
871                   (end (+ (tn-offset tn) (sc-element-size sc))))
872                  ((= offset end))
873                (declare (type index offset end))
874                (setf (svref (finite-sb-live-tns sb) offset) nil))))))
875     (do ((ref (vop-refs current) (tn-ref-next-ref ref)))
876         ((null ref))
877       (let ((ltn (tn-ref-load-tn ref)))
878         (when ltn
879           (let* ((sc (tn-sc ltn))
880                  (sb (sc-sb sc)))
881             (when (eq (sb-kind sb) :finite)
882               (let ((tns (finite-sb-live-tns sb)))
883                 (do ((offset (tn-offset ltn) (1+ offset))
884                      (end (+ (tn-offset ltn) (sc-element-size sc))))
885                     ((= offset end))
886                   (declare (type index offset end))
887                   (aver (null (svref tns offset)))))))))
888
889       (let* ((tn (tn-ref-tn ref))
890              (sc (tn-sc tn))
891              (sb (sc-sb sc)))
892         (when (eq (sb-kind sb) :finite)
893           (let ((tns (finite-sb-live-tns sb)))
894             (do ((offset (tn-offset tn) (1+ offset))
895                  (end (+ (tn-offset tn) (sc-element-size sc))))
896                 ((= offset end))
897               (declare (type index offset end))
898               (if (tn-ref-write-p ref)
899                   (setf (svref tns offset) nil)
900                   (let ((old (svref tns offset)))
901                     (aver (or (null old) (eq old tn)))
902                     (setf (svref tns offset) tn)))))))))
903
904   (setq *live-vop* vop)
905   (values))
906
907 ;;; This is kind of like OFFSET-CONFLICTS-IN-SB, except that it uses
908 ;;; the VOP refs to determine whether a Load-TN for OP could be packed
909 ;;; in the specified location, disregarding conflicts with TNs not
910 ;;; referenced by this VOP. There is a conflict if either:
911 ;;;  1. The reference is a result, and the same location is either:
912 ;;;     -- Used by some other result.
913 ;;;     -- Used in any way after the reference (exclusive).
914 ;;;  2. The reference is an argument, and the same location is either:
915 ;;;     -- Used by some other argument.
916 ;;;     -- Used in any way before the reference (exclusive).
917 ;;;
918 ;;; In 1 (and 2) above, the first bullet corresponds to result-result
919 ;;; (and argument-argument) conflicts. We need this case because there
920 ;;; aren't any TN-REFs to represent the implicit reading of results or
921 ;;; writing of arguments.
922 ;;;
923 ;;; The second bullet corresponds to conflicts with temporaries or
924 ;;; between arguments and results.
925 ;;;
926 ;;; We consider both the TN-REF-TN and the TN-REF-LOAD-TN (if any) to
927 ;;; be referenced simultaneously and in the same way. This causes
928 ;;; load-TNs to appear live to the beginning (or end) of the VOP, as
929 ;;; appropriate.
930 ;;;
931 ;;; We return a conflicting TN if there is a conflict.
932 (defun load-tn-offset-conflicts-in-sb (op sb offset)
933   (declare (type tn-ref op) (type finite-sb sb) (type index offset))
934   (aver (eq (sb-kind sb) :finite))
935   (let ((vop (tn-ref-vop op)))
936     (labels ((tn-overlaps (tn)
937                (let ((sc (tn-sc tn))
938                      (tn-offset (tn-offset tn)))
939                  (when (and (eq (sc-sb sc) sb)
940                             (<= tn-offset offset)
941                             (< offset
942                                (the index
943                                     (+ tn-offset (sc-element-size sc)))))
944                    tn)))
945              (same (ref)
946                (let ((tn (tn-ref-tn ref))
947                      (ltn (tn-ref-load-tn ref)))
948                  (or (tn-overlaps tn)
949                      (and ltn (tn-overlaps ltn)))))
950              (is-op (ops)
951                (do ((ops ops (tn-ref-across ops)))
952                    ((null ops) nil)
953                  (let ((found (same ops)))
954                    (when (and found (not (eq ops op)))
955                      (return found)))))
956              (is-ref (refs end)
957                (do ((refs refs (tn-ref-next-ref refs)))
958                    ((eq refs end) nil)
959                  (let ((found (same refs)))
960                  (when found (return found))))))
961       (declare (inline is-op is-ref tn-overlaps))
962       (if (tn-ref-write-p op)
963           (or (is-op (vop-results vop))
964               (is-ref (vop-refs vop) op))
965           (or (is-op (vop-args vop))
966               (is-ref (tn-ref-next-ref op) nil))))))
967
968 ;;; Iterate over all the elements in the SB that would be allocated by
969 ;;; allocating a TN in SC at Offset, checking for conflict with
970 ;;; load-TNs or other TNs (live in the LIVE-TNS, which must be set
971 ;;; up.) We also return true if there aren't enough locations after
972 ;;; Offset to hold a TN in SC. If Ignore-Live is true, then we ignore
973 ;;; the live-TNs, considering only references within Op's VOP.
974 ;;;
975 ;;; We return a conflicting TN, or :OVERFLOW if the TN won't fit.
976 (defun load-tn-conflicts-in-sc (op sc offset ignore-live)
977   (let* ((sb (sc-sb sc))
978          (size (finite-sb-current-size sb)))
979     (do ((i offset (1+ i))
980          (end (+ offset (sc-element-size sc))))
981         ((= i end) nil)
982       (declare (type index i end))
983       (let ((res (or (when (>= i size) :overflow)
984                      (and (not ignore-live)
985                           (svref (finite-sb-live-tns sb) i))
986                      (load-tn-offset-conflicts-in-sb op sb i))))
987         (when res (return res))))))
988
989 ;;; If a load-TN for OP is targeted to a legal location in SC, then
990 ;;; return the offset, otherwise return NIL. We see whether the target
991 ;;; of the operand is packed, and try that location. There isn't any
992 ;;; need to chain down the target path, since everything is packed
993 ;;; now.
994 ;;;
995 ;;; We require the target to be in SC (and not merely to overlap with
996 ;;; SC). This prevents SC information from being lost in load TNs (we
997 ;;; won't pack a load TN in ANY-REG when it is targeted to a
998 ;;; DESCRIPTOR-REG.) This shouldn't hurt the code as long as all
999 ;;; relevant overlapping SCs are allowed in the operand SC
1000 ;;; restriction.
1001 (defun find-load-tn-target (op sc)
1002   (declare (inline member))
1003   (let ((target (tn-ref-target op)))
1004     (when target
1005       (let* ((tn (tn-ref-tn target))
1006              (loc (tn-offset tn)))
1007         (if (and (eq (tn-sc tn) sc)
1008                  (member (the index loc) (sc-locations sc))
1009                  (not (load-tn-conflicts-in-sc op sc loc nil)))
1010             loc
1011             nil)))))
1012
1013 ;;; Select a legal location for a load TN for Op in SC. We just
1014 ;;; iterate over the SC's locations. If we can't find a legal
1015 ;;; location, return NIL.
1016 (defun select-load-tn-location (op sc)
1017   (declare (type tn-ref op) (type sc sc))
1018
1019   ;; Check any target location first.
1020   (let ((target (tn-ref-target op)))
1021     (when target
1022       (let* ((tn (tn-ref-tn target))
1023              (loc (tn-offset tn)))
1024         (when (and (eq (sc-sb sc) (sc-sb (tn-sc tn)))
1025                    (member (the index loc) (sc-locations sc))
1026                    (not (load-tn-conflicts-in-sc op sc loc nil)))
1027               (return-from select-load-tn-location loc)))))
1028
1029   (dolist (loc (sc-locations sc) nil)
1030     (unless (load-tn-conflicts-in-sc op sc loc nil)
1031       (return loc))))
1032
1033 (defevent unpack-tn "Unpacked a TN to satisfy operand SC restriction.")
1034
1035 ;;; Make TN's location the same as for its save TN (allocating a save
1036 ;;; TN if necessary.) Delete any save/restore code that has been
1037 ;;; emitted thus far. Mark all blocks containing references as needing
1038 ;;; to be repacked.
1039 (defun unpack-tn (tn)
1040   (event unpack-tn)
1041   (let ((stn (or (tn-save-tn tn)
1042                  (pack-save-tn tn))))
1043     (setf (tn-sc tn) (tn-sc stn))
1044     (setf (tn-offset tn) (tn-offset stn))
1045     (flet ((zot (refs)
1046              (do ((ref refs (tn-ref-next ref)))
1047                  ((null ref))
1048                (let ((vop (tn-ref-vop ref)))
1049                  (if (eq (vop-info-name (vop-info vop)) 'move-operand)
1050                      (delete-vop vop)
1051                      (pushnew (vop-block vop) *repack-blocks*))))))
1052       (zot (tn-reads tn))
1053       (zot (tn-writes tn))))
1054
1055   (values))
1056
1057 (defevent unpack-fallback "Unpacked some operand TN.")
1058
1059 ;;; This is called by PACK-LOAD-TN where there isn't any location free
1060 ;;; that we can pack into. What we do is move some live TN in one of
1061 ;;; the specified SCs to memory, then mark all blocks that reference
1062 ;;; the TN as needing repacking. If we succeed, we throw to UNPACKED-TN.
1063 ;;; If we fail, we return NIL.
1064 ;;;
1065 ;;; We can unpack any live TN that appears in the NORMAL-TNs list
1066 ;;; (isn't wired or restricted.) We prefer to unpack TNs that are not
1067 ;;; used by the VOP. If we can't find any such TN, then we unpack some
1068 ;;; argument or result TN. The only way we can fail is if all
1069 ;;; locations in SC are used by load-TNs or temporaries in VOP.
1070 (defun unpack-for-load-tn (sc op)
1071   (declare (type sc sc) (type tn-ref op))
1072   (let ((sb (sc-sb sc))
1073         (normal-tns (ir2-component-normal-tns
1074                      (component-info *component-being-compiled*)))
1075         (node (vop-node (tn-ref-vop op)))
1076         (fallback nil))
1077     (flet ((unpack-em (victims)
1078              (pushnew (vop-block (tn-ref-vop op)) *repack-blocks*)
1079              (dolist (victim victims)
1080                (event unpack-tn node)
1081                (unpack-tn victim))
1082              (throw 'unpacked-tn nil)))
1083       (dolist (loc (sc-locations sc))
1084         (declare (type index loc))
1085         (block SKIP
1086           (collect ((victims nil adjoin))
1087             (do ((i loc (1+ i))
1088                  (end (+ loc (sc-element-size sc))))
1089                 ((= i end))
1090               (declare (type index i end))
1091               (let ((victim (svref (finite-sb-live-tns sb) i)))
1092                 (when victim
1093                   (unless (find-in #'tn-next victim normal-tns)
1094                     (return-from SKIP))
1095                   (victims victim))))
1096
1097             (let ((conf (load-tn-conflicts-in-sc op sc loc t)))
1098               (cond ((not conf)
1099                      (unpack-em (victims)))
1100                     ((eq conf :overflow))
1101                     ((not fallback)
1102                      (cond ((find conf (victims))
1103                             (setq fallback (victims)))
1104                            ((find-in #'tn-next conf normal-tns)
1105                             (setq fallback (list conf))))))))))
1106
1107       (when fallback
1108         (event unpack-fallback node)
1109         (unpack-em fallback))))
1110
1111   nil)
1112
1113 ;;; Try to pack a load TN in the SCs indicated by Load-SCs. If we run
1114 ;;; out of SCs, then we unpack some TN and try again. We return the
1115 ;;; packed load TN.
1116 ;;;
1117 ;;; Note: we allow a Load-TN to be packed in the target location even
1118 ;;; if that location is in a SC not allowed by the primitive type.
1119 ;;; (The SC must still be allowed by the operand restriction.) This
1120 ;;; makes move VOPs more efficient, since we won't do a move from the
1121 ;;; stack into a non-descriptor any-reg through a descriptor argument
1122 ;;; load-TN. This does give targeting some real semantics, making it
1123 ;;; not a pure advisory to pack. It allows pack to do some packing it
1124 ;;; wouldn't have done before.
1125 (defun pack-load-tn (load-scs op)
1126   (declare (type sc-vector load-scs) (type tn-ref op))
1127   (let ((vop (tn-ref-vop op)))
1128     (compute-live-tns (vop-block vop) vop))
1129
1130   (let* ((tn (tn-ref-tn op))
1131          (ptype (tn-primitive-type tn))
1132          (scs (svref load-scs (sc-number (tn-sc tn)))))
1133     (let ((current-scs scs)
1134           (allowed ()))
1135       (loop
1136         (cond
1137          ((null current-scs)
1138           (unless allowed
1139             (no-load-scs-allowed-by-primitive-type-error op))
1140           (dolist (sc allowed)
1141             (unpack-for-load-tn sc op))
1142           (failed-to-pack-load-tn-error allowed op))
1143         (t
1144          (let* ((sc (svref *backend-sc-numbers* (pop current-scs)))
1145                 (target (find-load-tn-target op sc)))
1146            (when (or target (sc-allowed-by-primitive-type sc ptype))
1147              (let ((loc (or target
1148                             (select-load-tn-location op sc))))
1149                (when loc
1150                  (let ((res (make-tn 0 :load nil sc)))
1151                    (setf (tn-offset res) loc)
1152                    (return res))))
1153              (push sc allowed)))))))))
1154
1155 ;;; Scan a list of load-SCs vectors and a list of TN-REFS threaded by
1156 ;;; TN-REF-ACROSS. When we find a reference whose TN doesn't satisfy
1157 ;;; the restriction, we pack a Load-TN and load the operand into it.
1158 ;;; If a load-tn has already been allocated, we can assume that the
1159 ;;; restriction is satisfied.
1160 #!-sb-fluid (declaim (inline check-operand-restrictions))
1161 (defun check-operand-restrictions (scs ops)
1162   (declare (list scs) (type (or tn-ref null) ops))
1163
1164   ;; Check the targeted operands first.
1165   (do ((scs scs (cdr scs))
1166        (op ops (tn-ref-across op)))
1167       ((null scs))
1168       (let ((target (tn-ref-target op)))
1169         (when target
1170            (let* ((load-tn (tn-ref-load-tn op))
1171                   (load-scs (svref (car scs)
1172                                    (sc-number
1173                                     (tn-sc (or load-tn (tn-ref-tn op)))))))
1174              (if load-tn
1175                  (aver (eq load-scs t))
1176                (unless (eq load-scs t)
1177                        (setf (tn-ref-load-tn op)
1178                              (pack-load-tn (car scs) op))))))))
1179
1180   (do ((scs scs (cdr scs))
1181        (op ops (tn-ref-across op)))
1182       ((null scs))
1183       (let ((target (tn-ref-target op)))
1184         (unless target
1185            (let* ((load-tn (tn-ref-load-tn op))
1186                   (load-scs (svref (car scs)
1187                                    (sc-number
1188                                     (tn-sc (or load-tn (tn-ref-tn op)))))))
1189              (if load-tn
1190                  (aver (eq load-scs t))
1191                (unless (eq load-scs t)
1192                        (setf (tn-ref-load-tn op)
1193                              (pack-load-tn (car scs) op))))))))
1194
1195   (values))
1196
1197 ;;; Scan the VOPs in BLOCK, looking for operands whose SC restrictions
1198 ;;; aren't satisfied. We do the results first, since they are
1199 ;;; evaluated later, and our conflict analysis is a backward scan.
1200 (defun pack-load-tns (block)
1201   (catch 'unpacked-tn
1202     (let ((*live-block* nil)
1203           (*live-vop* nil))
1204       (do ((vop (ir2-block-last-vop block) (vop-prev vop)))
1205           ((null vop))
1206         (let ((info (vop-info vop)))
1207           (check-operand-restrictions (vop-info-result-load-scs info)
1208                                       (vop-results vop))
1209           (check-operand-restrictions (vop-info-arg-load-scs info)
1210                                       (vop-args vop))))))
1211   (values))
1212 \f
1213 ;;;; targeting
1214
1215 ;;; Link the TN-REFS READ and WRITE together using the TN-REF-TARGET
1216 ;;; when this seems like a good idea. Currently we always do, as this
1217 ;;; increases the success of load-TN targeting.
1218 (defun target-if-desirable (read write)
1219   (declare (type tn-ref read write))
1220   ;; As per the comments at the definition of TN-REF-TARGET, read and
1221   ;; write refs are always paired, with TARGET in the read pointing to
1222   ;; the write and vice versa.
1223   (aver (eq (tn-ref-write-p read)
1224             (not (tn-ref-write-p write))))
1225   (setf (tn-ref-target read) write)
1226   (setf (tn-ref-target write) read))
1227
1228 ;;; If TN can be packed into SC so as to honor a preference to TARGET,
1229 ;;; then return the offset to pack at, otherwise return NIL. TARGET
1230 ;;; must be already packed.
1231 (defun check-ok-target (target tn sc)
1232   (declare (type tn target tn) (type sc sc) (inline member))
1233   (let* ((loc (tn-offset target))
1234          (target-sc (tn-sc target))
1235          (target-sb (sc-sb target-sc)))
1236     (declare (type index loc))
1237     ;; We can honor a preference if:
1238     ;; -- TARGET's location is in SC's locations.
1239     ;; -- The element sizes of the two SCs are the same.
1240     ;; -- TN doesn't conflict with target's location.
1241     (if (and (eq target-sb (sc-sb sc))
1242              (or (eq (sb-kind target-sb) :unbounded)
1243                  (member loc (sc-locations sc)))
1244              (= (sc-element-size target-sc) (sc-element-size sc))
1245              (not (conflicts-in-sc tn sc loc))
1246              (zerop (mod loc (sc-alignment sc))))
1247         loc
1248         nil)))
1249
1250 ;;; Scan along the target path from TN, looking at readers or writers.
1251 ;;; When we find a packed TN, return CHECK-OK-TARGET of that TN. If
1252 ;;; there is no target, or if the TN has multiple readers (writers),
1253 ;;; then we return NIL. We also always return NIL after 10 iterations
1254 ;;; to get around potential circularity problems.
1255 ;;;
1256 ;;; FIXME: (30 minutes of reverse engineering?) It'd be nice to
1257 ;;; rewrite the header comment here to explain the interface and its
1258 ;;; motivation, and move remarks about implementation details (like
1259 ;;; 10!) inside.
1260 (defun find-ok-target-offset (tn sc)
1261   (declare (type tn tn) (type sc sc))
1262   (flet ((frob-slot (slot-fun)
1263            (declare (type function slot-fun))
1264            (let ((count 10)
1265                  (current tn))
1266              (declare (type index count))
1267              (loop
1268               (let ((refs (funcall slot-fun current)))
1269                 (unless (and (plusp count)
1270                              refs
1271                              (not (tn-ref-next refs)))
1272                   (return nil))
1273                 (let ((target (tn-ref-target refs)))
1274                   (unless target (return nil))
1275                   (setq current (tn-ref-tn target))
1276                   (when (tn-offset current)
1277                     (return (check-ok-target current tn sc)))
1278                   (decf count)))))))
1279     (declare (inline frob-slot)) ; until DYNAMIC-EXTENT works
1280     (or (frob-slot #'tn-reads)
1281         (frob-slot #'tn-writes))))
1282 \f
1283 ;;;; location selection
1284
1285 ;;; Select some location for TN in SC, returning the offset if we
1286 ;;; succeed, and NIL if we fail.
1287 ;;;
1288 ;;; For :UNBOUNDED SCs just find the smallest correctly aligned offset
1289 ;;; where the TN doesn't conflict with the TNs that have already been
1290 ;;; packed. For :FINITE SCs try to pack the TN into the most heavily
1291 ;;; used locations first (as estimated in FIND-LOCATION-USAGE).
1292 ;;;
1293 ;;; Historically SELECT-LOCATION tried did the opposite and tried to
1294 ;;; distribute the TNs evenly across the available locations. At least
1295 ;;; on register-starved architectures (x86) this seems to be a bad
1296 ;;; strategy. -- JES 2004-09-11
1297 (defun select-location (tn sc &key use-reserved-locs optimize)
1298   (declare (type tn tn) (type sc sc) (inline member))
1299   (let* ((sb (sc-sb sc))
1300          (element-size (sc-element-size sc))
1301          (alignment (sc-alignment sc))
1302          (align-mask (1- alignment))
1303          (size (finite-sb-current-size sb)))
1304     (flet ((attempt-location (start-offset)
1305              (dotimes (i element-size
1306                        (return-from select-location start-offset))
1307                (declare (type index i))
1308                (let ((offset (+ start-offset i)))
1309                  (when (offset-conflicts-in-sb tn sb offset)
1310                    (return (logandc2 (the index (+ (the index (1+ offset))
1311                                                    align-mask))
1312                                      align-mask)))))))
1313       (if (eq (sb-kind sb) :unbounded)
1314           (loop with offset = 0
1315                 until (> (+ offset element-size) size) do
1316                 (setf offset (attempt-location offset)))
1317           (let ((locations (sc-locations sc)))
1318             (when optimize
1319               (setf locations
1320                     (stable-sort (copy-list locations) #'>
1321                                  :key (lambda (location-offset)
1322                                         (loop for offset from location-offset
1323                                               repeat element-size
1324                                               maximize (svref
1325                                                         (finite-sb-always-live-count sb)
1326                                                         offset))))))
1327             (dolist (offset locations)
1328               (when (or use-reserved-locs
1329                         (not (member offset
1330                                      (sc-reserve-locations sc))))
1331                 (attempt-location offset))))))))
1332
1333 ;;; If a save TN, return the saved TN, otherwise return TN. This is
1334 ;;; useful for getting the conflicts of a TN that might be a save TN.
1335 (defun original-tn (tn)
1336   (declare (type tn tn))
1337   (if (member (tn-kind tn) '(:save :save-once :specified-save))
1338       (tn-save-tn tn)
1339       tn))
1340 \f
1341 ;;;; pack interface
1342
1343 ;;; Attempt to pack TN in all possible SCs, first in the SC chosen by
1344 ;;; representation selection, then in the alternate SCs in the order
1345 ;;; they were specified in the SC definition. If the TN-COST is
1346 ;;; negative, then we don't attempt to pack in SCs that must be saved.
1347 ;;; If Restricted, then we can only pack in TN-SC, not in any
1348 ;;; Alternate-SCs.
1349 ;;;
1350 ;;; If we are attempting to pack in the SC of the save TN for a TN
1351 ;;; with a :SPECIFIED-SAVE TN, then we pack in that location, instead
1352 ;;; of allocating a new stack location.
1353 (defun pack-tn (tn restricted optimize)
1354   (declare (type tn tn))
1355   (let* ((original (original-tn tn))
1356          (fsc (tn-sc tn))
1357          (alternates (unless restricted (sc-alternate-scs fsc)))
1358          (save (tn-save-tn tn))
1359          (specified-save-sc
1360           (when (and save
1361                      (eq (tn-kind save) :specified-save))
1362             (tn-sc save))))
1363     (do ((sc fsc (pop alternates)))
1364         ((null sc)
1365          (failed-to-pack-error tn restricted))
1366       (when (eq sc specified-save-sc)
1367         (unless (tn-offset save)
1368           (pack-tn save nil optimize))
1369         (setf (tn-offset tn) (tn-offset save))
1370         (setf (tn-sc tn) (tn-sc save))
1371         (return))
1372       (when (or restricted
1373                 (not (and (minusp (tn-cost tn)) (sc-save-p sc))))
1374         (let ((loc (or (find-ok-target-offset original sc)
1375                        (select-location original sc)
1376                        (and restricted
1377                             (select-location original sc :use-reserved-locs t))
1378                        (when (eq (sb-kind (sc-sb sc)) :unbounded)
1379                          (grow-sc sc)
1380                          (or (select-location original sc)
1381                              (error "failed to pack after growing SC?"))))))
1382           (when loc
1383             (add-location-conflicts original sc loc optimize)
1384             (setf (tn-sc tn) sc)
1385             (setf (tn-offset tn) loc)
1386             (return))))))
1387   (values))
1388
1389 ;;; Pack a wired TN, checking that the offset is in bounds for the SB,
1390 ;;; and that the TN doesn't conflict with some other TN already packed
1391 ;;; in that location. If the TN is wired to a location beyond the end
1392 ;;; of a :UNBOUNDED SB, then grow the SB enough to hold the TN.
1393 ;;;
1394 ;;; ### Checking for conflicts is disabled for :SPECIFIED-SAVE TNs.
1395 ;;; This is kind of a hack to make specifying wired stack save
1396 ;;; locations for local call arguments (such as OLD-FP) work, since
1397 ;;; the caller and callee OLD-FP save locations may conflict when the
1398 ;;; save locations don't really (due to being in different frames.)
1399 (defun pack-wired-tn (tn optimize)
1400   (declare (type tn tn))
1401   (let* ((sc (tn-sc tn))
1402          (sb (sc-sb sc))
1403          (offset (tn-offset tn))
1404          (end (+ offset (sc-element-size sc)))
1405          (original (original-tn tn)))
1406     (when (> end (finite-sb-current-size sb))
1407       (unless (eq (sb-kind sb) :unbounded)
1408         (error "~S is wired to a location that is out of bounds." tn))
1409       (grow-sc sc end))
1410
1411     ;; For non-x86 ports the presence of a save-tn associated with a
1412     ;; tn is used to identify the old-fp and return-pc tns. It depends
1413     ;; on the old-fp and return-pc being passed in registers.
1414     #!-(or x86 x86-64)
1415     (when (and (not (eq (tn-kind tn) :specified-save))
1416                (conflicts-in-sc original sc offset))
1417       (error "~S is wired to a location that it conflicts with." tn))
1418
1419     ;; Use the above check, but only print a verbose warning. This can
1420     ;; be helpful for debugging the x86 port.
1421     #+nil
1422     (when (and (not (eq (tn-kind tn) :specified-save))
1423                (conflicts-in-sc original sc offset))
1424           (format t "~&* Pack-wired-tn possible conflict:~%  ~
1425                      tn: ~S; tn-kind: ~S~%  ~
1426                      sc: ~S~%  ~
1427                      sb: ~S; sb-name: ~S; sb-kind: ~S~%  ~
1428                      offset: ~S; end: ~S~%  ~
1429                      original ~S~%  ~
1430                      tn-save-tn: ~S; tn-kind of tn-save-tn: ~S~%"
1431                   tn (tn-kind tn) sc
1432                   sb (sb-name sb) (sb-kind sb)
1433                   offset end
1434                   original
1435                   (tn-save-tn tn) (tn-kind (tn-save-tn tn))))
1436
1437     ;; On the x86 ports the old-fp and return-pc are often passed on
1438     ;; the stack so the above hack for the other ports does not always
1439     ;; work. Here the old-fp and return-pc tns are identified by being
1440     ;; on the stack in their standard save locations.
1441     #!+(or x86 x86-64)
1442     (when (and (not (eq (tn-kind tn) :specified-save))
1443                (not (and (string= (sb-name sb) "STACK")
1444                          (or (= offset 0)
1445                              (= offset 1))))
1446                (conflicts-in-sc original sc offset))
1447       (error "~S is wired to a location that it conflicts with." tn))
1448
1449     (add-location-conflicts original sc offset optimize)))
1450
1451 (defevent repack-block "Repacked a block due to TN unpacking.")
1452
1453 ;;; KLUDGE: Prior to SBCL version 0.8.9.xx, this function was known as
1454 ;;; PACK-BEFORE-GC-HOOK, but was non-functional since approximately
1455 ;;; version 0.8.3.xx since the removal of GC hooks from the system.
1456 ;;; This currently (as of 2004-04-12) runs now after every call to
1457 ;;; PACK, rather than -- as was originally intended -- once per GC
1458 ;;; cycle; this is probably non-optimal, and might require tuning,
1459 ;;; maybe to be called when the data structures exceed a certain size,
1460 ;;; or maybe once every N times.  The KLUDGE is that this rewrite has
1461 ;;; done nothing to improve the reentrance or threadsafety of the
1462 ;;; compiler; it still fails to be callable from several threads at
1463 ;;; the same time.
1464 ;;;
1465 ;;; Brief experiments indicate that during a compilation cycle this
1466 ;;; causes about 10% more consing, and takes about 1%-2% more time.
1467 ;;;
1468 ;;; -- CSR, 2004-04-12
1469 (defun clean-up-pack-structures ()
1470   (dolist (sb *backend-sb-list*)
1471     (unless (eq (sb-kind sb) :non-packed)
1472       (let ((size (sb-size sb)))
1473         (fill (finite-sb-always-live sb) nil)
1474         (setf (finite-sb-always-live sb)
1475               (make-array size
1476                           :initial-element
1477                           #-sb-xc #*
1478                           ;; The cross-compiler isn't very good at
1479                           ;; dumping specialized arrays, so we delay
1480                           ;; construction of this SIMPLE-BIT-VECTOR
1481                           ;; until runtime.
1482                           #+sb-xc (make-array 0 :element-type 'bit)))
1483         (setf (finite-sb-always-live-count sb)
1484               (make-array size
1485                           :initial-element
1486                           #-sb-xc #*
1487                           ;; Ibid
1488                           #+sb-xc (make-array 0 :element-type 'fixnum)))
1489
1490         (fill (finite-sb-conflicts sb) nil)
1491         (setf (finite-sb-conflicts sb)
1492               (make-array size :initial-element '#()))
1493
1494         (fill (finite-sb-live-tns sb) nil)
1495         (setf (finite-sb-live-tns sb)
1496               (make-array size :initial-element nil))))))
1497
1498 (defun pack (component)
1499   (unwind-protect
1500        (let ((optimize nil)
1501              (2comp (component-info component)))
1502          (init-sb-vectors component)
1503
1504          ;; Determine whether we want to do more expensive packing by
1505          ;; checking whether any blocks in the component have (> SPEED
1506          ;; COMPILE-SPEED).
1507          ;;
1508          ;; FIXME: This means that a declaration can have a minor
1509          ;; effect even outside its scope, and as the packing is done
1510          ;; component-globally it'd be tricky to use strict scoping. I
1511          ;; think this is still acceptable since it's just a tradeoff
1512          ;; between compilation speed and allocation quality and
1513          ;; doesn't affect the semantics of the generated code in any
1514          ;; way. -- JES 2004-10-06
1515          (do-ir2-blocks (block component)
1516            (when (policy (block-last (ir2-block-block block))
1517                          (> speed compilation-speed))
1518              (setf optimize t)
1519              (return)))
1520
1521          ;; Call the target functions.
1522          (do-ir2-blocks (block component)
1523            (do ((vop (ir2-block-start-vop block) (vop-next vop)))
1524                ((null vop))
1525              (let ((target-fun (vop-info-target-fun (vop-info vop))))
1526                (when target-fun
1527                  (funcall target-fun vop)))))
1528
1529          ;; Pack wired TNs first.
1530          (do ((tn (ir2-component-wired-tns 2comp) (tn-next tn)))
1531              ((null tn))
1532            (pack-wired-tn tn optimize))
1533
1534          ;; Pack restricted component TNs.
1535          (do ((tn (ir2-component-restricted-tns 2comp) (tn-next tn)))
1536              ((null tn))
1537            (when (eq (tn-kind tn) :component)
1538              (pack-tn tn t optimize)))
1539
1540          ;; Pack other restricted TNs.
1541          (do ((tn (ir2-component-restricted-tns 2comp) (tn-next tn)))
1542              ((null tn))
1543            (unless (tn-offset tn)
1544              (pack-tn tn t optimize)))
1545
1546          ;; Assign costs to normal TNs so we know which ones should
1547          ;; always be packed on the stack.
1548          (when *pack-assign-costs*
1549            (assign-tn-costs component)
1550            (assign-tn-depths component))
1551
1552          ;; Allocate normal TNs, starting with the TNs that are used
1553          ;; in deep loops.
1554          (collect ((tns))
1555            (do-ir2-blocks (block component)
1556              (let ((ltns (ir2-block-local-tns block)))
1557                (do ((i (1- (ir2-block-local-tn-count block)) (1- i)))
1558                    ((minusp i))
1559                  (declare (fixnum i))
1560                  (let ((tn (svref ltns i)))
1561                    (unless (or (null tn)
1562                                (eq tn :more)
1563                                (tn-offset tn))
1564                      ;; If loop analysis has been disabled we might as
1565                      ;; well revert to the old behaviour of just
1566                      ;; packing TNs linearly as they appear.
1567                      (unless *loop-analyze*
1568                        (pack-tn tn nil optimize))
1569                      (tns tn))))))
1570            (dolist (tn (stable-sort (tns)
1571                                     (lambda (a b)
1572                                       (cond
1573                                         ((> (tn-loop-depth a)
1574                                             (tn-loop-depth b))
1575                                          t)
1576                                         ((= (tn-loop-depth a)
1577                                             (tn-loop-depth b))
1578                                          (> (tn-cost a) (tn-cost b)))
1579                                         (t nil)))))
1580              (unless (tn-offset tn)
1581                (pack-tn tn nil optimize))))
1582
1583          ;; Pack any leftover normal TNs. This is to deal with :MORE TNs,
1584          ;; which could possibly not appear in any local TN map.
1585          (do ((tn (ir2-component-normal-tns 2comp) (tn-next tn)))
1586              ((null tn))
1587            (unless (tn-offset tn)
1588              (pack-tn tn nil optimize)))
1589
1590          ;; Do load TN packing and emit saves.
1591          (let ((*repack-blocks* nil))
1592            (cond ((and optimize *pack-optimize-saves*)
1593                   (optimized-emit-saves component)
1594                   (do-ir2-blocks (block component)
1595                     (pack-load-tns block)))
1596                  (t
1597                   (do-ir2-blocks (block component)
1598                     (emit-saves block)
1599                     (pack-load-tns block))))
1600            (loop
1601               (unless *repack-blocks* (return))
1602               (let ((orpb *repack-blocks*))
1603                 (setq *repack-blocks* nil)
1604                 (dolist (block orpb)
1605                   (event repack-block)
1606                   (pack-load-tns block)))))
1607
1608          (values))
1609     (clean-up-pack-structures)))