Add MAKE-DUMMY-FDEFN function.
[sbcl.git] / src / compiler / stack.lisp
blobfcbd1e7a78fb220812bd248a962b373334e4bdb9
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.
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.
18 (in-package "SB!C")
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))
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))))
45 (setf (ir2-block-pushed 2block) (pushed))))
46 (values))
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))
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)))
68 ;; Blocks are numbered in reverse DFO order, so the "lowest common
69 ;; dominator" of a set of blocks is the closest dominator of all of
70 ;; the blocks.
71 (defun find-lowest-common-dominator (blocks)
72 ;; FIXME: NIL is defined as a valid value for BLOCK-DOMINATORS,
73 ;; meaning "all blocks in component". Actually handle this case.
74 (let ((common-dominators (copy-sset (block-dominators (first blocks)))))
75 (dolist (block (rest blocks))
76 (sset-intersection common-dominators (block-dominators block)))
77 (let ((lowest-dominator))
78 (do-sset-elements (dominator common-dominators lowest-dominator)
79 (when (or (not lowest-dominator)
80 (< (sset-element-number dominator)
81 (sset-element-number lowest-dominator)))
82 (setf lowest-dominator dominator))))))
84 ;;; Carefully back-propagate DX LVARs from the start of their
85 ;;; environment to where they are allocated, along all code paths
86 ;;; which actually allocate said LVARs.
87 (defun back-propagate-one-dx-lvar (block dx-lvar)
88 (declare (type cblock block)
89 (type lvar dx-lvar))
90 ;; We have to back-propagate the lifetime of DX-LVAR to its USEs,
91 ;; but only along the paths which actually USE it. The naive
92 ;; solution (which we're going with for now) is a depth-first search
93 ;; over an arbitrarily complex chunk of flow graph that is known to
94 ;; have a single entry block.
95 (let* ((use-blocks (mapcar #'node-block (find-uses dx-lvar)))
96 (start-block (find-lowest-common-dominator
97 (list* block use-blocks))))
98 (labels ((mark-lvar-live-on-path (arc-list)
99 (dolist (arc arc-list)
100 (let ((2block (block-info (car arc))))
101 (pushnew dx-lvar (ir2-block-end-stack 2block))
102 (pushnew dx-lvar (ir2-block-start-stack 2block)))))
103 (back-propagate-pathwise (current-block path)
104 (cond
105 ((member current-block use-blocks)
106 ;; The LVAR is live on exit from a use-block, but
107 ;; not on entry.
108 (pushnew dx-lvar (ir2-block-end-stack
109 (block-info current-block)))
110 (mark-lvar-live-on-path path))
111 ;; Don't go back past START-BLOCK.
112 ((not (eq current-block start-block))
113 (dolist (pred-block (block-pred current-block))
114 (let ((new-arc (cons current-block pred-block)))
115 (declare (dynamic-extent new-arc))
116 ;; Never follow the same path segment twice.
117 (unless (member new-arc path :test #'equal)
118 (let ((new-path (list* new-arc path)))
119 (declare (dynamic-extent new-path))
120 (back-propagate-pathwise pred-block new-path)))))))))
121 (back-propagate-pathwise block nil))))
123 (defun back-propagate-dx-lvars (block dx-lvars)
124 (declare (type cblock block)
125 (type list dx-lvars))
126 (dolist (dx-lvar dx-lvars)
127 (back-propagate-one-dx-lvar block dx-lvar)))
129 ;;; Update information on stacks of unknown-values LVARs on the
130 ;;; boundaries of BLOCK. Return true if the start stack has been
131 ;;; changed.
133 ;;; An LVAR is live at the end iff it is live at some of blocks, which
134 ;;; BLOCK can transfer control to. There are two kind of control
135 ;;; transfers: normal, expressed with BLOCK-SUCC, and NLX.
136 (defun update-uvl-live-sets (block)
137 (declare (type cblock block))
138 (let* ((2block (block-info block))
139 (original-start (ir2-block-start-stack 2block))
140 (end (ir2-block-end-stack 2block))
141 (new-end end))
142 (dolist (succ (block-succ block))
143 (setq new-end (merge-uvl-live-sets new-end
144 ;; Don't back-propagate DX
145 ;; LVARs automatically,
146 ;; they're handled specially.
147 (remove-if #'lvar-dynamic-extent
148 (ir2-block-start-stack (block-info succ))))))
149 (map-block-nlxes (lambda (nlx-info)
150 (let* ((nle (nlx-info-target nlx-info))
151 (nle-start-stack (ir2-block-start-stack
152 (block-info nle)))
153 (exit-lvar (nlx-info-lvar nlx-info))
154 (next-stack (if exit-lvar
155 (remove exit-lvar nle-start-stack)
156 nle-start-stack)))
157 (setq new-end (merge-uvl-live-sets
158 new-end next-stack))))
159 block
160 (lambda (dx-cleanup)
161 (dolist (lvar (cleanup-info dx-cleanup))
162 (do-uses (generator lvar)
163 (let* ((block (node-block generator))
164 (2block (block-info block)))
165 ;; DX objects, living in the LVAR, are alive in
166 ;; the environment, protected by the CLEANUP. We
167 ;; also cannot move them (because, in general, we
168 ;; cannot track all references to them).
169 ;; Therefore, everything, allocated deeper than a
170 ;; DX object -- that is, before the DX object --
171 ;; should be kept alive until the object is
172 ;; deallocated.
174 ;; Since DX generators end their blocks, we can
175 ;; find out UVLs allocated before them by looking
176 ;; at the stack at the end of the block.
178 ;; FIXME: This is not quite true: REFs to DX
179 ;; closures don't end their blocks!
180 (setq new-end (merge-uvl-live-sets
181 new-end (ir2-block-end-stack 2block)))
182 (setq new-end (merge-uvl-live-sets
183 new-end (ir2-block-pushed 2block))))))))
185 (setf (ir2-block-end-stack 2block) new-end)
187 ;; If a block starts with an "entry DX" node (the start of a DX
188 ;; environment) then we need to back-propagate the DX LVARs to
189 ;; their allocation sites. We need to be clever about this
190 ;; because some code paths may not allocate all of the DX LVARs.
192 ;; FIXME: Use BLOCK-FLAG to make this happen only once.
193 (let ((first-node (ctran-next (block-start block))))
194 (when (typep first-node 'entry)
195 (let ((cleanup (entry-cleanup first-node)))
196 (when (eq (cleanup-kind cleanup) :dynamic-extent)
197 (back-propagate-dx-lvars block (cleanup-info cleanup))))))
199 (let ((start new-end))
200 (setq start (set-difference start (ir2-block-pushed 2block)))
201 (setq start (merge-uvl-live-sets start (ir2-block-popped 2block)))
203 ;; We cannot delete unused UVLs during NLX, so all UVLs live at
204 ;; ENTRY will be actually live at NLE.
206 ;; BUT, UNWIND-PROTECTor is called in the environment, which has
207 ;; nothing in common with the environment of its entry. So we
208 ;; fictively compute its stack from the containing cleanups, but
209 ;; do not propagate additional LVARs from the entry, thus
210 ;; preveting bogus stack cleanings.
212 ;; TODO: Insert a check that no values are discarded in UWP. Or,
213 ;; maybe, we just don't need to create NLX-ENTRY for UWP?
214 (when (and (eq (component-head (block-component block))
215 (first (block-pred block)))
216 (not (bind-p (block-start-node block))))
217 (let* ((nlx-info (nle-block-nlx-info block))
218 (cleanup (nlx-info-cleanup nlx-info)))
219 (unless (eq (cleanup-kind cleanup) :unwind-protect)
220 (let* ((entry-block (node-block (cleanup-mess-up cleanup)))
221 (entry-stack (ir2-block-start-stack (block-info entry-block))))
222 (setq start (merge-uvl-live-sets start entry-stack))))))
224 (when *check-consistency*
225 (aver (subsetp original-start start)))
226 (cond ((subsetp start original-start)
227 nil)
229 (setf (ir2-block-start-stack 2block) start)
230 t)))))
233 ;;;; Ordering of live UVL stacks
235 (defun ordered-list-intersection (ordered-list other-list)
236 (loop for item in ordered-list
237 when (memq item other-list)
238 collect item))
240 (defun ordered-list-union (ordered-list-1 ordered-list-2)
241 (labels ((sub-union (ol1 ol2 result)
242 (cond ((and (null ol1) (null ol2))
243 result)
244 ((and (null ol1) ol2)
245 (sub-union ol1 (cdr ol2) (cons (car ol2) result)))
246 ((and ol1 (null ol2))
247 (sub-union (cdr ol1) ol2 (cons (car ol1) result)))
248 ((eq (car ol1) (car ol2))
249 (sub-union (cdr ol1) (cdr ol2) (cons (car ol1) result)))
250 ((memq (car ol1) ol2)
251 (sub-union ol1 (cdr ol2) (cons (car ol2) result)))
253 (sub-union (cdr ol1) ol2 (cons (car ol1) result))))))
254 (nreverse (sub-union ordered-list-1 ordered-list-2 nil))))
256 ;;; Put UVLs on the start/end stacks of BLOCK in the right order. PRED
257 ;;; is a predecessor of BLOCK with already sorted stacks; if all UVLs
258 ;;; being live at the BLOCK start are live in PRED we just need to
259 ;;; delete killed UVLs, otherwise we need (thanks to conditional or
260 ;;; nested DX) to set a total order for the UVLs live at the end of
261 ;;; all predecessors.
262 (defun order-block-uvl-sets (block pred)
263 (let* ((2block (block-info block))
264 (pred-end-stack (ir2-block-end-stack (block-info pred)))
265 (start (ir2-block-start-stack 2block))
266 (start-stack (ordered-list-intersection pred-end-stack start))
267 (end (ir2-block-end-stack 2block)))
269 (when (not (subsetp start start-stack))
270 ;; If BLOCK is a control-flow join for DX allocation paths with
271 ;; different sets of DX LVARs being pushed then we cannot
272 ;; process it correctly until all of its predecessors have been
273 ;; processed.
274 (unless (every #'block-flag (block-pred block))
275 (return-from order-block-uvl-sets nil))
276 ;; If we are in the conditional-DX control-flow join case then
277 ;; we need to find an order for START-STACK that is compatible
278 ;; with all of our predecessors.
279 (dolist (end-stack (mapcar #'ir2-block-end-stack
280 (mapcar #'block-info
281 (block-pred block))))
282 (setf pred-end-stack
283 (ordered-list-union pred-end-stack end-stack)))
284 (setf start-stack (ordered-list-intersection pred-end-stack start)))
286 (when *check-consistency*
287 (aver (subsetp start start-stack)))
288 (setf (ir2-block-start-stack 2block) start-stack)
290 (let* ((last (block-last block))
291 (tailp-lvar (if (node-tail-p last) (node-lvar last)))
292 (end-stack start-stack))
293 (dolist (pop (ir2-block-popped 2block))
294 (aver (eq pop (car end-stack)))
295 (pop end-stack))
296 (dolist (push (ir2-block-pushed 2block))
297 (aver (not (memq push end-stack)))
298 (push push end-stack))
299 (aver (subsetp end end-stack))
300 (when (and tailp-lvar
301 (eq (ir2-lvar-kind (lvar-info tailp-lvar)) :unknown))
302 (aver (eq tailp-lvar (first end-stack)))
303 (pop end-stack))
304 (setf (ir2-block-end-stack 2block) end-stack)))
307 (defun order-uvl-sets (component)
308 (clear-flags component)
309 ;; KLUDGE: Workaround for lp#308914: we keep track of number of blocks
310 ;; needing repeats, and bug out if we get stuck.
311 (loop with head = (component-head component)
312 with todo = 0
313 with last-todo = 0
314 do (psetq last-todo todo
315 todo 0)
316 do (do-blocks (block component)
317 (unless (block-flag block)
318 (let ((pred (find-if #'block-flag (block-pred block))))
319 (when (and (eq pred head)
320 (not (bind-p (block-start-node block))))
321 (let ((entry (nle-block-entry-block block)))
322 (setq pred (if (block-flag entry) entry nil))))
323 (if (and pred
324 (order-block-uvl-sets block pred))
325 (setf (block-flag block) t)
326 (incf todo)))))
327 do (when (= last-todo todo)
328 ;; If the todo count is the same as on last iteration and
329 ;; there are still blocks to do, it means we are stuck,
330 ;; which in turn means the unmarked blocks are actually
331 ;; unreachable and should have been eliminated by DCE,
332 ;; and will very likely cause problems with later parts
333 ;; of STACK analysis, so abort now if we're in trouble.
334 (aver (not (plusp todo))))
335 while (plusp todo)))
337 ;;; This is called when we discover that the stack-top unknown-values
338 ;;; lvar at the end of BLOCK1 is different from that at the start of
339 ;;; BLOCK2 (its successor).
341 ;;; We insert a call to a funny function in a new cleanup block
342 ;;; introduced between BLOCK1 and BLOCK2. Since control analysis and
343 ;;; LTN have already run, we must do make an IR2 block, then do
344 ;;; ADD-TO-EMIT-ORDER and LTN-ANALYZE-BELATED-BLOCK on the new
345 ;;; block. The new block is inserted after BLOCK1 in the emit order.
347 ;;; If the control transfer between BLOCK1 and BLOCK2 represents a
348 ;;; tail-recursive return or a non-local exit, then the cleanup code
349 ;;; will never actually be executed. It doesn't seem to be worth the
350 ;;; risk of trying to optimize this, since this rarely happens and
351 ;;; wastes only space.
352 (defun insert-stack-cleanups (block1 block2)
353 (declare (type cblock block1 block2))
354 (collect ((cleanup-code))
355 (labels ((find-popped (before after)
356 ;; Returns (VALUES popped last-popped rest), where
357 ;; BEFORE = (APPEND popped rest) and
358 ;; (EQ (FIRST rest) (FIRST after))
359 (if (null after)
360 (values before (first (last before)) nil)
361 (loop with first-preserved = (car after)
362 for last-popped = nil then maybe-popped
363 for rest on before
364 for maybe-popped = (car rest)
365 while (neq maybe-popped first-preserved)
366 collect maybe-popped into popped
367 finally (return (values popped last-popped rest)))))
368 (discard (before-stack after-stack)
369 (cond
370 ((eq (car before-stack) (car after-stack))
371 (binding* ((moved-count (mismatch before-stack after-stack)
372 :exit-if-null)
373 ((moved qmoved)
374 (loop for moved-lvar in before-stack
375 repeat moved-count
376 collect moved-lvar into moved
377 collect `',moved-lvar into qmoved
378 finally (return (values moved qmoved))))
379 (q-last-moved (car (last qmoved)))
380 ((nil last-nipped rest)
381 (find-popped (nthcdr moved-count before-stack)
382 (nthcdr moved-count after-stack))))
383 (cleanup-code
384 `(%nip-values ',last-nipped ,q-last-moved
385 ,@qmoved))
386 (discard (nconc moved rest) after-stack)))
388 (multiple-value-bind (popped last-popped rest)
389 (find-popped before-stack after-stack)
390 (declare (ignore popped))
391 (cleanup-code `(%pop-values ',last-popped))
392 (discard rest after-stack)))))
393 (dummy-allocations (before-stack after-stack)
394 (loop
395 for previous-lvar = nil then lvar
396 for lvar in after-stack
397 unless (memq lvar before-stack)
398 do (cleanup-code
399 `(%dummy-dx-alloc ',lvar ',previous-lvar)))))
400 (let* ((end-stack (ir2-block-end-stack (block-info block1)))
401 (start-stack (ir2-block-start-stack (block-info block2)))
402 (pruned-start-stack (ordered-list-intersection
403 start-stack end-stack)))
404 (discard end-stack pruned-start-stack)
405 (dummy-allocations pruned-start-stack start-stack)
406 (when (cleanup-code)
407 (let* ((block (insert-cleanup-code block1 block2
408 (block-start-node block2)
409 `(progn ,@(cleanup-code))))
410 (2block (make-ir2-block block)))
411 (setf (block-info block) 2block)
412 ;; Set the start and end stacks to make traces less
413 ;; confusing. Purely cosmetic.
414 (setf (ir2-block-start-stack 2block) end-stack)
415 (setf (ir2-block-end-stack 2block) start-stack)
416 (add-to-emit-order 2block (block-info block1))
417 (ltn-analyze-belated-block block))))))
419 (values))
421 ;;;; stack analysis
423 ;;; Return a list of all the blocks containing genuine uses of one of
424 ;;; the RECEIVERS (blocks) and DX-LVARS. Exits are excluded, since
425 ;;; they don't drop through to the receiver.
426 (defun find-pushing-blocks (receivers dx-lvars)
427 (declare (list receivers dx-lvars))
428 (collect ((res nil adjoin))
429 (dolist (rec receivers)
430 (dolist (pop (ir2-block-popped (block-info rec)))
431 (do-uses (use pop)
432 (unless (exit-p use)
433 (res (node-block use))))))
434 (dolist (dx-lvar dx-lvars)
435 (do-uses (use dx-lvar)
436 (res (node-block use))))
437 (res)))
439 ;;; Analyze the use of unknown-values and DX lvars in COMPONENT,
440 ;;; inserting cleanup code to discard values that are generated but
441 ;;; never received and to set appropriate bounds for DX values that
442 ;;; are cleaned up but never allocated. This phase doesn't need to be
443 ;;; run when Values-Receivers and Dx-Lvars are null, i.e. there are no
444 ;;; unknown-values lvars used across block boundaries and no DX LVARs.
445 (defun stack-analyze (component)
446 (declare (type component component))
447 (let* ((2comp (component-info component))
448 (receivers (ir2-component-values-receivers 2comp))
449 (generators (find-pushing-blocks receivers
450 (component-dx-lvars component))))
452 (dolist (block generators)
453 (find-pushed-lvars block))
455 ;;; Compute sets of live UVLs and DX LVARs
456 (loop for did-something = nil
457 do (do-blocks-backwards (block component)
458 (when (update-uvl-live-sets block)
459 (setq did-something t)))
460 while did-something)
462 (order-uvl-sets component)
464 (do-blocks (block component)
465 (let ((top (ir2-block-end-stack (block-info block))))
466 (dolist (succ (block-succ block))
467 (when (and (block-start succ)
468 (not (eq (ir2-block-start-stack (block-info succ))
469 top)))
470 (insert-stack-cleanups block succ))))))
472 (values))