0.8.7.16:
[sbcl.git] / src / compiler / dfo.lisp
1 ;;;; This file contains the code that finds the initial components and
2 ;;;; DFO, and recomputes the DFO if it is invalidated.
3
4 ;;;; This software is part of the SBCL system. See the README file for
5 ;;;; more information.
6 ;;;;
7 ;;;; This software is derived from the CMU CL system, which was
8 ;;;; written at Carnegie Mellon University and released into the
9 ;;;; public domain. The software is in the public domain and is
10 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
11 ;;;; files for more information.
12
13 (in-package "SB!C")
14
15 ;;; Find the DFO for a component, deleting any unreached blocks and
16 ;;; merging any other components we reach. We repeatedly iterate over
17 ;;; the entry points, since new ones may show up during the walk.
18 (declaim (ftype (function (component) (values)) find-dfo))
19 (defun find-dfo (component)
20   (clear-flags component)
21   (setf (component-reanalyze component) nil)
22   (let ((head (component-head component)))
23     (do ()
24         ((dolist (ep (block-succ head) t)
25            (unless (or (block-flag ep) (block-delete-p ep))
26              (find-dfo-aux ep head component)
27              (return nil))))))
28   (let ((num 0))
29     (declare (fixnum num))
30     (do-blocks-backwards (block component :both)
31       (if (block-flag block)
32           (setf (block-number block) (incf num))
33           (delete-block-lazily block)))
34     (clean-component component (component-head component)))
35   (values))
36
37 ;;; Move all the code and entry points from OLD to NEW. The code in
38 ;;; OLD is inserted at the head of NEW. This is also called during LET
39 ;;; conversion when we are about in insert the body of a LET in a
40 ;;; different component. [A local call can be to a different component
41 ;;; before FIND-INITIAL-DFO runs.]
42 (declaim (ftype (function (component component) (values)) join-components))
43 (defun join-components (new old)
44   (aver (eq (component-kind new) (component-kind old)))
45   (let ((old-head (component-head old))
46         (old-tail (component-tail old))
47         (head (component-head new))
48         (tail (component-tail new)))
49
50     (do-blocks (block old)
51       (setf (block-flag block) nil)
52       (setf (block-component block) new))
53
54     (let ((old-next (block-next old-head))
55           (old-last (block-prev old-tail))
56           (next (block-next head)))
57       (unless (eq old-next old-tail)
58         (setf (block-next head) old-next)
59         (setf (block-prev old-next) head)
60
61         (setf (block-prev next) old-last)
62         (setf (block-next old-last) next))
63
64       (setf (block-next old-head) old-tail)
65       (setf (block-prev old-tail) old-head))
66
67     (setf (component-lambdas new)
68           (nconc (component-lambdas old) (component-lambdas new)))
69     (setf (component-lambdas old) nil)
70     (setf (component-new-functionals new)
71           (nconc (component-new-functionals old)
72                  (component-new-functionals new)))
73     (setf (component-new-functionals old) nil)
74
75     (dolist (xp (block-pred old-tail))
76       (unlink-blocks xp old-tail)
77       (link-blocks xp tail))
78     (dolist (ep (block-succ old-head))
79       (unlink-blocks old-head ep)
80       (link-blocks head ep)))
81   (values))
82
83 ;;; Do a depth-first walk from BLOCK, inserting ourself in the DFO
84 ;;; after HEAD. If we somehow find ourselves in another component,
85 ;;; then we join that component to our component.
86 (declaim (ftype (function (cblock cblock component) (values)) find-dfo-aux))
87 (defun find-dfo-aux (block head component)
88   (unless (eq (block-component block) component)
89     (join-components component (block-component block)))
90   (unless (or (block-flag block) (block-delete-p block))
91     (setf (block-flag block) t)
92     (dolist (succ (block-succ block))
93       (find-dfo-aux succ head component))
94     (remove-from-dfo block)
95     (add-to-dfo block head))
96   (values))
97
98 ;;; This function is called on each block by FIND-INITIAL-DFO-AUX
99 ;;; before it walks the successors. It looks at the home CLAMBDA's
100 ;;; BIND block to see whether that block is in some other component:
101 ;;; -- If the block is in the initial component, then do
102 ;;;    DFO-SCAVENGE-DEPENDENCY-GRAPH on the home function to move it
103 ;;;    into COMPONENT.
104 ;;; -- If the block is in some other component, join COMPONENT into
105 ;;;    it and return that component.
106 ;;; -- If the home function is deleted, do nothing. BLOCK must
107 ;;;    eventually be discovered to be unreachable as well. This can
108 ;;;    happen when we have a NLX into a function with no references.
109 ;;;    The escape function still has refs (in the deleted function).
110 ;;;
111 ;;; This ensures that all the blocks in a given environment will be in
112 ;;; the same component, even when they might not seem reachable from
113 ;;; the environment entry. Consider the case of code that is only
114 ;;; reachable from a non-local exit.
115 (defun scavenge-home-dependency-graph (block component)
116   (declare (type cblock block) (type component component))
117   (let ((home-lambda (block-home-lambda block)))
118     (if (eq (functional-kind home-lambda) :deleted)
119         component
120         (let ((home-component (lambda-component home-lambda)))
121           (cond ((eq (component-kind home-component) :initial)
122                  (dfo-scavenge-dependency-graph home-lambda component))
123                 ((eq home-component component)
124                  component)
125                 (t
126                  (join-components home-component component)
127                  home-component))))))
128
129 ;;; This is somewhat similar to FIND-DFO-AUX, except that it merges
130 ;;; the current component with any strange component, rather than the
131 ;;; other way around. This is more efficient in the common case where
132 ;;; the current component doesn't have much stuff in it.
133 ;;;
134 ;;; We return the current component as a result, allowing the caller
135 ;;; to detect when the old current component has been merged with
136 ;;; another.
137 ;;;
138 ;;; We walk blocks in initial components as though they were already
139 ;;; in the current component, moving them to the current component in
140 ;;; the process. The blocks are inserted at the head of the current
141 ;;; component.
142 (defun find-initial-dfo-aux (block component)
143   (declare (type cblock block) (type component component))
144   (let ((this (block-component block)))
145     (cond
146      ((not (or (eq this component)
147                (eq (component-kind this) :initial)))
148       (join-components this component)
149       this)
150      ((block-flag block) component)
151      (t
152       (setf (block-flag block) t)
153       (let ((current (scavenge-home-dependency-graph block component)))
154         (dolist (succ (block-succ block))
155           (setq current (find-initial-dfo-aux succ current)))
156         (remove-from-dfo block)
157         (add-to-dfo block (component-head current))
158         current)))))
159
160 ;;; Return a list of all the home lambdas that reference FUN (may
161 ;;; contain duplications).
162 ;;;
163 ;;; References to functions which local call analysis could not (or
164 ;;; were chosen not) to local call convert will appear as references
165 ;;; to XEP lambdas. We can ignore references to XEPs that appear in
166 ;;; :TOPLEVEL components, since environment analysis goes to special
167 ;;; effort to allow closing over of values from a separate top level
168 ;;; component. (And now that HAS-EXTERNAL-REFERENCES-P-ness
169 ;;; generalizes :TOPLEVEL-ness, we ignore those too.) All other
170 ;;; references must cause components to be joined.
171 ;;;
172 ;;; References in deleted functions are also ignored, since this code
173 ;;; will be deleted eventually.
174 (defun find-reference-funs (fun)
175   (collect ((res))
176     (dolist (ref (leaf-refs fun))
177       (let* ((home (node-home-lambda ref))
178              (home-kind (functional-kind home))
179              (home-externally-visible-p
180               (or (eq home-kind :toplevel)
181                   (functional-has-external-references-p home))))
182         (unless (or (and home-externally-visible-p
183                          (eq (functional-kind fun) :external))
184                     (eq home-kind :deleted))
185           (res home))))
186     (res)))
187
188 ;;; If CLAMBDA is already in COMPONENT, just return that
189 ;;; component. Otherwise, move the code for CLAMBDA and all lambdas it
190 ;;; physically depends on (either because of calls or because of
191 ;;; closure relationships) into COMPONENT, or possibly into another
192 ;;; COMPONENT that we find to be related. Return whatever COMPONENT we
193 ;;; actually merged into.
194 ;;;
195 ;;; (Note: The analogous CMU CL code only scavenged call-based
196 ;;; dependencies, not closure dependencies. That seems to've been by
197 ;;; oversight, not by design, as per the bug reported by WHN on
198 ;;; cmucl-imp ca. 2001-11-29 and explained by DTC shortly after.)
199 ;;;
200 ;;; If the function is in an initial component, then we move its head
201 ;;; and tail to COMPONENT and add it to COMPONENT's lambdas. It is
202 ;;; harmless to move the tail (even though the return might be
203 ;;; unreachable) because if the return is unreachable it (and its
204 ;;; successor link) will be deleted in the post-deletion pass.
205 ;;;
206 ;;; We then do a FIND-DFO-AUX starting at the head of CLAMBDA. If this
207 ;;; flow-graph walk encounters another component (which can only
208 ;;; happen due to a non-local exit), then we move code into that
209 ;;; component instead. We then recurse on all functions called from
210 ;;; CLAMBDA, moving code into whichever component the preceding call
211 ;;; returned.
212 ;;;
213 ;;; If CLAMBDA is in the initial component, but the BLOCK-FLAG is set
214 ;;; in the bind block, then we just return COMPONENT, since we must
215 ;;; have already reached this function in the current walk (or the
216 ;;; component would have been changed).
217 ;;;
218 ;;; If the function is an XEP, then we also walk all functions that
219 ;;; contain references to the XEP. This is done so that environment
220 ;;; analysis doesn't need to cross component boundaries. This also
221 ;;; ensures that conversion of a full call to a local call won't
222 ;;; result in a need to join components, since the components will
223 ;;; already be one.
224 (defun dfo-scavenge-dependency-graph (clambda component)
225   (declare (type clambda clambda) (type component component))
226   (assert (not (eql (lambda-kind clambda) :deleted)))
227   (let* ((bind-block (node-block (lambda-bind clambda)))
228          (old-lambda-component (block-component bind-block))
229          (return (lambda-return clambda)))
230     (cond
231      ((eq old-lambda-component component)
232       component)
233      ((not (eq (component-kind old-lambda-component) :initial))
234       (join-components old-lambda-component component)
235       old-lambda-component)
236      ((block-flag bind-block)
237       component)
238      (t
239       (push clambda (component-lambdas component))
240       (setf (component-lambdas old-lambda-component)
241             (delete clambda (component-lambdas old-lambda-component)))
242       (link-blocks (component-head component) bind-block)
243       (unlink-blocks (component-head old-lambda-component) bind-block)
244       (when return
245         (let ((return-block (node-block return)))
246           (link-blocks return-block (component-tail component))
247           (unlink-blocks return-block (component-tail old-lambda-component))))
248       (let ((res (find-initial-dfo-aux bind-block component)))
249         (declare (type component res))
250         ;; Scavenge related lambdas.
251         (labels ((scavenge-lambda (clambda)
252                    (setf res
253                          (dfo-scavenge-dependency-graph (lambda-home clambda)
254                                                         res)))
255                  (scavenge-possibly-deleted-lambda (clambda)
256                    (unless (eql (lambda-kind clambda) :deleted)
257                      (scavenge-lambda clambda)))
258                  ;; Scavenge call relationship.
259                  (scavenge-call (called-lambda)
260                    (scavenge-lambda called-lambda))
261                  ;; Scavenge closure over a variable: if CLAMBDA
262                  ;; refers to a variable whose home lambda is not
263                  ;; CLAMBDA, then the home lambda should be in the
264                  ;; same component as CLAMBDA. (sbcl-0.6.13, and CMU
265                  ;; CL, didn't do this, leading to the occasional
266                  ;; failure when physenv analysis, which is local to
267                  ;; each component, would bogusly conclude that a
268                  ;; closed-over variable was unused and thus delete
269                  ;; it. See e.g. cmucl-imp 2001-11-29.)
270                  (scavenge-closure-var (var)
271                    (unless (null (lambda-var-refs var)) ; unless var deleted
272                      (let ((var-home-home (lambda-home (lambda-var-home var))))
273                        (scavenge-possibly-deleted-lambda var-home-home))))
274                  ;; Scavenge closure over an entry for nonlocal exit.
275                  ;; This is basically parallel to closure over a
276                  ;; variable above.
277                  (scavenge-entry (entry)
278                    (declare (type entry entry))
279                    (let ((entry-home (node-home-lambda entry)))
280                      (scavenge-possibly-deleted-lambda entry-home))))
281           (dolist (cc (lambda-calls-or-closes clambda))
282             (etypecase cc
283               (clambda (scavenge-call cc))
284               (lambda-var (scavenge-closure-var cc))
285               (entry (scavenge-entry cc))))
286           (when (eq (lambda-kind clambda) :external)
287             (mapc #'scavenge-call (find-reference-funs clambda))))
288         ;; Voila.
289         res)))))
290
291 ;;; Return true if CLAMBDA either is an XEP or has EXITS to some of
292 ;;; its ENTRIES.
293 (defun has-xep-or-nlx (clambda)
294   (declare (type clambda clambda))
295   (or (eq (functional-kind clambda) :external)
296       (let ((entries (lambda-entries clambda)))
297         (and entries
298              (find-if #'entry-exits entries)))))
299
300 ;;; Compute the result of FIND-INITIAL-DFO given the list of all
301 ;;; resulting components. Components with a :TOPLEVEL lambda, but no
302 ;;; normal XEPs or potential non-local exits are marked as :TOPLEVEL.
303 ;;; If there is a :TOPLEVEL lambda, and also a normal XEP, then we
304 ;;; treat the component as normal, but also return such components in
305 ;;; a list as the third value. Components with no entry of any sort
306 ;;; are deleted.
307 (defun separate-toplevelish-components (components)
308   (declare (list components))
309   (collect ((real)
310             (top)
311             (real-top))
312     (dolist (component components)
313       (unless (eq (block-next (component-head component))
314                   (component-tail component))
315         (let* ((funs (component-lambdas component))
316                (has-top (find :toplevel funs :key #'functional-kind))
317                (has-external-references
318                 (some #'functional-has-external-references-p funs)))
319           (cond (;; The FUNCTIONAL-HAS-EXTERNAL-REFERENCES-P concept
320                  ;; is newer than the rest of this function, and
321                  ;; doesn't really seem to fit into its mindset. Here
322                  ;; we mark components which contain such FUNCTIONs
323                  ;; them as :COMPLEX-TOPLEVEL, since they do get
324                  ;; executed at run time, and since it's not valid to
325                  ;; delete them just because they don't have any
326                  ;; references from pure :TOPLEVEL components. -- WHN
327                  has-external-references
328                  (setf (component-kind component) :complex-toplevel)
329                  (real component)
330                  (real-top component))
331                 ((or (some #'has-xep-or-nlx funs)
332                      (and has-top (rest funs)))
333                  (setf (component-name component)
334                        (find-component-name component))
335                  (real component)
336                  (when has-top
337                    (setf (component-kind component) :complex-toplevel)
338                    (real-top component)))
339                 (has-top
340                  (setf (component-kind component) :toplevel)
341                  (setf (component-name component) "top level form")
342                  (top component))
343                 (t
344                  (delete-component component))))))
345
346     (values (real) (top) (real-top))))
347
348 ;;; COMPONENTs want strings for names, LEAF-DEBUG-NAMEs mightn't be
349 ;;; strings...
350 (defun component-name-from-functional-debug-name (functional)
351   (declare (type functional functional))
352   (let ((leaf-debug-name (leaf-debug-name functional)))
353     (the simple-string
354       (if (stringp leaf-debug-name)
355           leaf-debug-name
356           (debug-namify "function ~S" leaf-debug-name)))))
357
358 ;;; Given a list of top level lambdas, return
359 ;;;   (VALUES NONTOP-COMPONENTS TOP-COMPONENTS HAIRY-TOP-COMPONENTS).
360 ;;; Each of the three values returned is a list of COMPONENTs:
361 ;;;   NONTOP-COMPONENTS = non-top-level-ish COMPONENTs;
362 ;;;   TOP-COMPONENTS = top-level-ish COMPONENTs;
363 ;;;   HAIRY-TOP-COMPONENTS = a subset of NONTOP-COMPONENTS, those
364 ;;;    elements which include a top-level-ish lambda.
365 ;;;
366 ;;; We assign the DFO for each component, and delete any unreachable
367 ;;; blocks. We assume that the FLAGS have already been cleared.
368 (defun find-initial-dfo (toplevel-lambdas)
369   (declare (list toplevel-lambdas))
370   (collect ((components))
371     ;; We iterate over the lambdas in each initial component, trying
372     ;; to put each function in its own component, but joining it to
373     ;; an existing component if we find that there are references
374     ;; between them. Any code that is left in an initial component
375     ;; must be unreachable, so we can delete it. Stray links to the
376     ;; initial component tail (due to NIL function terminated blocks)
377     ;; are moved to the appropriate new component tail.
378     (dolist (toplevel-lambda toplevel-lambdas)
379       (let* ((old-component (lambda-component toplevel-lambda))
380              (old-component-lambdas (component-lambdas old-component))
381              (new-component nil))
382         (aver (member toplevel-lambda old-component-lambdas))
383         (dolist (component-lambda old-component-lambdas)
384           (aver (member (functional-kind component-lambda)
385                         '(:optional :external :toplevel nil :escape
386                                     :cleanup)))
387           (unless new-component
388             (setf new-component (make-empty-component))
389             (setf (component-name new-component)
390                   ;; This isn't necessarily an ideal name for the
391                   ;; component, since it might end up with multiple
392                   ;; lambdas in it, not just this one, but it does
393                   ;; seem a better name than just "<unknown>".
394                   (component-name-from-functional-debug-name
395                    component-lambda)))
396           (let ((res (dfo-scavenge-dependency-graph component-lambda
397                                                     new-component)))
398             (when (eq res new-component)
399               (aver (not (position new-component (components))))
400               (components new-component)
401               (setq new-component nil))))
402         (when (eq (component-kind old-component) :initial)
403           (aver (null (component-lambdas old-component)))
404           (let ((tail (component-tail old-component)))
405             (dolist (pred (block-pred tail))
406               (let ((pred-component (block-component pred)))
407                 (unless (eq pred-component old-component)
408                   (unlink-blocks pred tail)
409                   (link-blocks pred (component-tail pred-component))))))
410           (delete-component old-component))))
411
412     ;; When we are done, we assign DFNs.
413     (dolist (component (components))
414       (let ((num 0))
415         (declare (fixnum num))
416         (do-blocks-backwards (block component :both)
417           (setf (block-number block) (incf num)))))
418
419     ;; Pull out top-level-ish code.
420     (separate-toplevelish-components (components))))
421 \f
422 ;;; Insert the code in LAMBDA at the end of RESULT-LAMBDA.
423 (defun merge-1-toplevel-lambda (result-lambda lambda)
424   (declare (type clambda result-lambda lambda))
425
426   ;; Delete the lambda, and combine the LETs and entries.
427   (setf (functional-kind lambda) :deleted)
428   (dolist (let (lambda-lets lambda))
429     (setf (lambda-home let) result-lambda)
430     (setf (lambda-physenv let) (lambda-physenv result-lambda))
431     (push let (lambda-lets result-lambda)))
432   (setf (lambda-entries result-lambda)
433         (nconc (lambda-entries result-lambda)
434                (lambda-entries lambda)))
435
436   (let* ((bind (lambda-bind lambda))
437          (bind-block (node-block bind))
438          (component (block-component bind-block))
439          (result-component (lambda-component result-lambda))
440          (result-return-block (node-block (lambda-return result-lambda))))
441
442     ;; Move blocks into the new COMPONENT, and move any nodes directly
443     ;; in the old LAMBDA into the new one (with LETs implicitly moved
444     ;; by changing their home.)
445     (do-blocks (block component)
446       (do-nodes (node nil block)
447         (let ((lexenv (node-lexenv node)))
448           (when (eq (lexenv-lambda lexenv) lambda)
449             (setf (lexenv-lambda lexenv) result-lambda))))
450       (setf (block-component block) result-component))
451
452     ;; Splice the blocks into the new DFO, and unlink them from the
453     ;; old component head and tail. Non-return blocks that jump to the
454     ;; tail (NIL-returning calls) are switched to go to the new tail.
455     (let* ((head (component-head component))
456            (first (block-next head))
457            (tail (component-tail component))
458            (last (block-prev tail))
459            (prev (block-prev result-return-block)))
460       (setf (block-next prev) first)
461       (setf (block-prev first) prev)
462       (setf (block-next last) result-return-block)
463       (setf (block-prev result-return-block) last)
464       (dolist (succ (block-succ head))
465         (unlink-blocks head succ))
466       (dolist (pred (block-pred tail))
467         (unlink-blocks pred tail)
468         (let ((last (block-last pred)))
469           (unless (return-p last)
470             (aver (basic-combination-p last))
471             (link-blocks pred (component-tail result-component))))))
472
473     (let ((lambdas (component-lambdas component)))
474       (aver (and (null (rest lambdas))
475                  (eq (first lambdas) lambda))))
476
477     ;; Switch the end of the code from the return block to the start of
478     ;; the next chunk.
479     (dolist (pred (block-pred result-return-block))
480       (unlink-blocks pred result-return-block)
481       (link-blocks pred bind-block))
482     (unlink-node bind)
483
484     ;; If there is a return, then delete it (making the preceding node
485     ;; the last node) and link the block to the result return. There
486     ;; is always a preceding REF NIL node in top level lambdas.
487     (let ((return (lambda-return lambda)))
488       (when return
489         (link-blocks (node-block return) result-return-block)
490         (flush-dest (return-result return))
491         (unlink-node return)))))
492
493 ;;; Given a non-empty list of top level LAMBDAs, smash them into a
494 ;;; top level lambda and component, returning these as values. We use
495 ;;; the first lambda and its component, putting the other code in that
496 ;;; component and deleting the other lambdas.
497 (defun merge-toplevel-lambdas (lambdas)
498   (declare (cons lambdas))
499   (let* ((result-lambda (first lambdas))
500          (result-return (lambda-return result-lambda)))
501     (cond
502      (result-return
503
504       ;; Make sure the result's return node starts a block so that we
505       ;; can splice code in before it.
506       (let ((prev (node-prev
507                    (lvar-uses (return-result result-return)))))
508         (when (ctran-use prev)
509           (node-ends-block (ctran-use prev))))
510
511       (dolist (lambda (rest lambdas))
512         (merge-1-toplevel-lambda result-lambda lambda)))
513      (t
514       (dolist (lambda (rest lambdas))
515         (setf (functional-entry-fun lambda) nil)
516         (delete-component (lambda-component lambda)))))
517
518     (values (lambda-component result-lambda) result-lambda)))