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