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