1.0.15.10: ASSOC and MEMBER were broken for :KEY #'IDENTITY
[sbcl.git] / src / compiler / stack.lisp
1 ;;;; This file implements the stack analysis phase in the compiler. We
2 ;;;; analyse lifetime of dynamically allocated object packets on stack
3 ;;;; and insert cleanups where necessary.
4 ;;;;
5 ;;;; Currently there are two kinds of interesting stack packets: UVLs,
6 ;;;; whose use and destination lie in different blocks, and LVARs of
7 ;;;; constructors of dynamic-extent objects.
8
9 ;;;; This software is part of the SBCL system. See the README file for
10 ;;;; more information.
11 ;;;;
12 ;;;; This software is derived from the CMU CL system, which was
13 ;;;; written at Carnegie Mellon University and released into the
14 ;;;; public domain. The software is in the public domain and is
15 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
16 ;;;; files for more information.
17
18 (in-package "SB!C")
19 \f
20 ;;; Scan through BLOCK looking for uses of :UNKNOWN lvars that have
21 ;;; their DEST outside of the block. We do some checking to verify the
22 ;;; invariant that all pushes come after the last pop.
23 (defun find-pushed-lvars (block)
24   (let* ((2block (block-info block))
25          (popped (ir2-block-popped 2block))
26          (last-pop (if popped
27                        (lvar-dest (car (last popped)))
28                        nil)))
29     (collect ((pushed))
30       (let ((saw-last nil))
31         (do-nodes (node lvar block)
32           (when (eq node last-pop)
33             (setq saw-last t))
34
35           (when (and lvar
36                      (or (lvar-dynamic-extent lvar)
37                          (let ((dest (lvar-dest lvar))
38                                (2lvar (lvar-info lvar)))
39                            (and (not (eq (node-block dest) block))
40                                 2lvar
41                                 (eq (ir2-lvar-kind 2lvar) :unknown)))))
42             (aver (or saw-last (not last-pop)))
43             (pushed lvar))))
44
45       (setf (ir2-block-pushed 2block) (pushed))))
46   (values))
47 \f
48 ;;;; Computation of live UVL sets
49 (defun nle-block-nlx-info (block)
50   (let* ((start-node (block-start-node block))
51          (nlx-ref (ctran-next (node-next start-node)))
52          (nlx-info (constant-value (ref-leaf nlx-ref))))
53     nlx-info))
54 (defun nle-block-entry-block (block)
55   (let* ((nlx-info (nle-block-nlx-info block))
56          (mess-up (cleanup-mess-up (nlx-info-cleanup nlx-info)))
57          (entry-block (node-block mess-up)))
58     entry-block))
59
60 ;;; Add LVARs from LATE to EARLY; use EQ to check whether EARLY has
61 ;;; been changed.
62 (defun merge-uvl-live-sets (early late)
63   (declare (type list early late))
64   ;; FIXME: O(N^2)
65   (dolist (e late early)
66     (pushnew e early)))
67
68 ;;; Update information on stacks of unknown-values LVARs on the
69 ;;; boundaries of BLOCK. Return true if the start stack has been
70 ;;; changed.
71 ;;;
72 ;;; An LVAR is live at the end iff it is live at some of blocks, which
73 ;;; BLOCK can transfer control to. There are two kind of control
74 ;;; transfers: normal, expressed with BLOCK-SUCC, and NLX.
75 (defun update-uvl-live-sets (block)
76   (declare (type cblock block))
77   (let* ((2block (block-info block))
78          (original-start (ir2-block-start-stack 2block))
79          (end (ir2-block-end-stack 2block))
80          (new-end end))
81     (dolist (succ (block-succ block))
82       (setq new-end (merge-uvl-live-sets new-end
83                                          (ir2-block-start-stack (block-info succ)))))
84     (map-block-nlxes (lambda (nlx-info)
85                        (let* ((nle (nlx-info-target nlx-info))
86                               (nle-start-stack (ir2-block-start-stack
87                                                 (block-info nle)))
88                               (exit-lvar (nlx-info-lvar nlx-info))
89                               (next-stack (if exit-lvar
90                                               (remove exit-lvar nle-start-stack)
91                                               nle-start-stack)))
92                          (setq new-end (merge-uvl-live-sets
93                                         new-end next-stack))))
94                      block
95                      (lambda (dx-cleanup)
96                        (dolist (lvar (cleanup-info dx-cleanup))
97                          (let ((uses (lvar-uses lvar)))
98                            (dolist (generator (if (listp uses) uses (list uses)))
99                              (let* ((block (node-block generator))
100                                     (2block (block-info block)))
101                                ;; DX objects, living in the LVAR, are
102                                ;; alive in the environment, protected
103                                ;; by the CLEANUP. We also cannot move
104                                ;; them (because, in general, we cannot
105                                ;; track all references to
106                                ;; them). Therefore, everything,
107                                ;; allocated deeper than a DX object,
108                                ;; should be kept alive until the
109                                ;; object is deallocated.
110                                (setq new-end (merge-uvl-live-sets
111                                               new-end (ir2-block-end-stack 2block)))
112                                (setq new-end (merge-uvl-live-sets
113                                               new-end (ir2-block-pushed 2block)))))))))
114
115     (setf (ir2-block-end-stack 2block) new-end)
116
117     (let ((start new-end))
118       (setq start (set-difference start (ir2-block-pushed 2block)))
119       (setq start (merge-uvl-live-sets start (ir2-block-popped 2block)))
120
121       ;; We cannot delete unused UVLs during NLX, so all UVLs live at
122       ;; ENTRY will be actually live at NLE.
123       ;;
124       ;; BUT, UNWIND-PROTECTor is called in the environment, which has
125       ;; nothing in common with the environment of its entry. So we
126       ;; fictively compute its stack from the containing cleanups, but
127       ;; do not propagate additional LVARs from the entry, thus
128       ;; preveting bogus stack cleanings.
129       ;;
130       ;; TODO: Insert a check that no values are discarded in UWP. Or,
131       ;; maybe, we just don't need to create NLX-ENTRY for UWP?
132       (when (and (eq (component-head (block-component block))
133                      (first (block-pred block)))
134                  (not (bind-p (block-start-node block))))
135         (let* ((nlx-info (nle-block-nlx-info block))
136                (cleanup (nlx-info-cleanup nlx-info)))
137           (unless (eq (cleanup-kind cleanup) :unwind-protect)
138             (let* ((entry-block (node-block (cleanup-mess-up cleanup)))
139                    (entry-stack (ir2-block-start-stack (block-info entry-block))))
140               (setq start (merge-uvl-live-sets start entry-stack))))))
141
142       (when *check-consistency*
143         (aver (subsetp original-start start)))
144       (cond ((subsetp start original-start)
145              nil)
146             (t
147              (setf (ir2-block-start-stack 2block) start)
148              t)))))
149
150 \f
151 ;;;; Ordering of live UVL stacks
152
153 ;;; Put UVLs on the start/end stacks of BLOCK in the right order. PRED
154 ;;; is a predecessor of BLOCK with already sorted stacks; because all
155 ;;; UVLs being live at the BLOCK start are live in PRED, we just need
156 ;;; to delete dead UVLs.
157 (defun order-block-uvl-sets (block pred)
158   (let* ((2block (block-info block))
159          (pred-end-stack (ir2-block-end-stack (block-info pred)))
160          (start (ir2-block-start-stack 2block))
161          (start-stack (loop for lvar in pred-end-stack
162                             when (memq lvar start)
163                             collect lvar))
164          (end (ir2-block-end-stack 2block)))
165     (when *check-consistency*
166       (aver (subsetp start start-stack)))
167     (setf (ir2-block-start-stack 2block) start-stack)
168
169     (let* ((last (block-last block))
170            (tailp-lvar (if (node-tail-p last) (node-lvar last)))
171            (end-stack start-stack))
172       (dolist (pop (ir2-block-popped 2block))
173         (aver (eq pop (car end-stack)))
174         (pop end-stack))
175       (dolist (push (ir2-block-pushed 2block))
176         (aver (not (memq push end-stack)))
177         (push push end-stack))
178       (aver (subsetp end end-stack))
179       (when (and tailp-lvar
180                  (eq (ir2-lvar-kind (lvar-info tailp-lvar)) :unknown))
181         (aver (eq tailp-lvar (first end-stack)))
182         (pop end-stack))
183       (setf (ir2-block-end-stack 2block) end-stack))))
184
185 (defun order-uvl-sets (component)
186   (clear-flags component)
187   (loop with head = (component-head component)
188         with repeat-p do
189         (setq repeat-p nil)
190         (do-blocks (block component)
191           (unless (block-flag block)
192             (let ((pred (find-if #'block-flag (block-pred block))))
193               (when (and (eq pred head)
194                          (not (bind-p (block-start-node block))))
195                 (let ((entry (nle-block-entry-block block)))
196                   (setq pred (if (block-flag entry) entry nil))))
197               (cond (pred
198                      (setf (block-flag block) t)
199                      (order-block-uvl-sets block pred))
200                     (t
201                      (setq repeat-p t))))))
202         while repeat-p))
203 \f
204 ;;; This is called when we discover that the stack-top unknown-values
205 ;;; lvar at the end of BLOCK1 is different from that at the start of
206 ;;; BLOCK2 (its successor).
207 ;;;
208 ;;; We insert a call to a funny function in a new cleanup block
209 ;;; introduced between BLOCK1 and BLOCK2. Since control analysis and
210 ;;; LTN have already run, we must do make an IR2 block, then do
211 ;;; ADD-TO-EMIT-ORDER and LTN-ANALYZE-BELATED-BLOCK on the new
212 ;;; block. The new block is inserted after BLOCK1 in the emit order.
213 ;;;
214 ;;; If the control transfer between BLOCK1 and BLOCK2 represents a
215 ;;; tail-recursive return or a non-local exit, then the cleanup code
216 ;;; will never actually be executed. It doesn't seem to be worth the
217 ;;; risk of trying to optimize this, since this rarely happens and
218 ;;; wastes only space.
219 (defun discard-unused-values (block1 block2)
220   (declare (type cblock block1 block2))
221   (collect ((cleanup-code))
222     (labels ((find-popped (before after)
223                ;; Returns (VALUES popped last-popped rest), where
224                ;; BEFORE = (APPEND popped rest) and
225                ;; (EQ (FIRST rest) (FIRST after))
226                (if (null after)
227                    (values before (first (last before)) nil)
228                    (loop with first-preserved = (car after)
229                          for last-popped = nil then maybe-popped
230                          for rest on before
231                          for maybe-popped = (car rest)
232                          while (neq maybe-popped first-preserved)
233                          collect maybe-popped into popped
234                          finally (return (values popped last-popped rest)))))
235              (discard (before-stack after-stack)
236                (cond
237                  ((eq (car before-stack) (car after-stack))
238                   (binding* ((moved-count (mismatch before-stack after-stack)
239                                           :exit-if-null)
240                              ((moved qmoved)
241                               (loop for moved-lvar in before-stack
242                                     repeat moved-count
243                                     collect moved-lvar into moved
244                                     collect `',moved-lvar into qmoved
245                                     finally (return (values moved qmoved))))
246                              (q-last-moved (car (last qmoved)))
247                              ((nil last-nipped rest)
248                               (find-popped (nthcdr moved-count before-stack)
249                                            (nthcdr moved-count after-stack))))
250                     (cleanup-code
251                      `(%nip-values ',last-nipped ,q-last-moved
252                        ,@qmoved))
253                     (discard (nconc moved rest) after-stack)))
254                  (t
255                   (multiple-value-bind (popped last-popped rest)
256                       (find-popped before-stack after-stack)
257                     (declare (ignore popped))
258                     (cleanup-code `(%pop-values ',last-popped))
259                     (discard rest after-stack))))))
260       (discard (ir2-block-end-stack (block-info block1))
261                (ir2-block-start-stack (block-info block2))))
262     (when (cleanup-code)
263       (let* ((block (insert-cleanup-code block1 block2
264                                          (block-start-node block2)
265                                          `(progn ,@(cleanup-code))))
266              (2block (make-ir2-block block)))
267         (setf (block-info block) 2block)
268         (add-to-emit-order 2block (block-info block1))
269         (ltn-analyze-belated-block block))))
270
271   (values))
272 \f
273 ;;;; stack analysis
274
275 ;;; Return a list of all the blocks containing genuine uses of one of
276 ;;; the RECEIVERS (blocks) and DX-LVARS. Exits are excluded, since
277 ;;; they don't drop through to the receiver.
278 (defun find-pushing-blocks (receivers dx-lvars)
279   (declare (list receivers dx-lvars))
280   (collect ((res nil adjoin))
281     (dolist (rec receivers)
282       (dolist (pop (ir2-block-popped (block-info rec)))
283         (do-uses (use pop)
284           (unless (exit-p use)
285             (res (node-block use))))))
286     (dolist (dx-lvar dx-lvars)
287       (do-uses (use dx-lvar)
288         (res (node-block use))))
289     (res)))
290
291 ;;; Analyze the use of unknown-values and DX lvars in COMPONENT,
292 ;;; inserting cleanup code to discard values that are generated but
293 ;;; never received. This phase doesn't need to be run when
294 ;;; Values-Receivers and Dx-Lvars are null, i.e. there are no
295 ;;; unknown-values lvars used across block boundaries and no DX LVARs.
296 (defun stack-analyze (component)
297   (declare (type component component))
298   (let* ((2comp (component-info component))
299          (receivers (ir2-component-values-receivers 2comp))
300          (generators (find-pushing-blocks receivers
301                                           (component-dx-lvars component))))
302
303     (dolist (block generators)
304       (find-pushed-lvars block))
305
306     ;;; Compute sets of live UVLs and DX LVARs
307     (loop for did-something = nil
308           do (do-blocks-backwards (block component)
309                (when (update-uvl-live-sets block)
310                  (setq did-something t)))
311           while did-something)
312
313     (order-uvl-sets component)
314
315     (do-blocks (block component)
316       (let ((top (ir2-block-end-stack (block-info block))))
317         (dolist (succ (block-succ block))
318           (when (and (block-start succ)
319                      (not (eq (ir2-block-start-stack (block-info succ))
320                               top)))
321             (discard-unused-values block succ))))))
322
323   (values))