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