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