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