dd304c7e753fa18c9afcb403b1e469245677b760
[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) ())
73     (setf (component-new-functions new)
74           (nconc (component-new-functions old) (component-new-functions new)))
75     (setf (component-new-functions old) ())
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 before it
103 ;;; walks the successors. It looks at the home lambda's bind block to see
104 ;;; whether that block is in some other component:
105 ;;; -- If the block is in the initial component, then do DFO-Walk-Call-Graph on
106 ;;;    the home function to move it into component.
107 ;;; -- If the block is in some other component, join Component into it and
108 ;;;    return that component.
109 ;;; -- If the home function is deleted, do nothing. Block must eventually be
110 ;;;    discovered to be unreachable as well. This can happen when we have a
111 ;;;    NLX into a function with no references. The escape function still has
112 ;;;    refs (in the deleted function).
113 ;;;
114 ;;; This ensures that all the blocks in a given environment will be in the same
115 ;;; component, even when they might not seem reachable from the environment
116 ;;; entry. Consider the case of code that is only reachable from a non-local
117 ;;; exit.
118 (defun walk-home-call-graph (block component)
119   (declare (type cblock block) (type component component))
120   (let ((home (block-home-lambda block)))
121     (if (eq (functional-kind home) :deleted)
122         component
123         (let* ((bind-block (node-block (lambda-bind home)))
124                (home-component (block-component bind-block)))
125           (cond ((eq (component-kind home-component) :initial)
126                  (dfo-walk-call-graph home component))
127                 ((eq home-component component)
128                  component)
129                 (t
130                  (join-components home-component component)
131                  home-component))))))
132
133 ;;; Somewhat similar to Find-DFO-Aux, except that it merges the current
134 ;;; component with any strange component, rather than the other way around.
135 ;;; This is more efficient in the common case where the current component
136 ;;; doesn't have much stuff in it.
137 ;;;
138 ;;; We return the current component as a result, allowing the caller to
139 ;;; detect when the old current component has been merged with another.
140 ;;;
141 ;;; We walk blocks in initial components as though they were already in the
142 ;;; current component, moving them to the current component in the process.
143 ;;; The blocks are inserted at the head of the current component.
144 (defun find-initial-dfo-aux (block component)
145   (declare (type cblock block) (type component component))
146   (let ((this (block-component block)))
147     (cond
148      ((not (or (eq this component)
149                (eq (component-kind this) :initial)))
150       (join-components this component)
151       this)
152      ((block-flag block) component)
153      (t
154       (setf (block-flag block) t)
155       (let ((current (walk-home-call-graph block component)))
156         (dolist (succ (block-succ block))
157           (setq current (find-initial-dfo-aux succ current)))
158         
159         (remove-from-dfo block)
160         (add-to-dfo block (component-head current))
161         current)))))
162
163 ;;; Return a list of all the home lambdas that reference Fun (may contain
164 ;;; duplications).
165 ;;;
166 ;;; References to functions which local call analysis could not (or were
167 ;;; chosen not) to local call convert will appear as references to XEP lambdas.
168 ;;; We can ignore references to XEPs that appear in :TOP-LEVEL components,
169 ;;; since environment analysis goes to special effort to allow closing over of
170 ;;; values from a separate top-level component. All other references must
171 ;;; cause components to be joined.
172 ;;;
173 ;;; References in deleted functions are also ignored, since this code will be
174 ;;; deleted eventually.
175 (defun find-reference-functions (fun)
176   (collect ((res))
177     (dolist (ref (leaf-refs fun))
178       (let* ((home (node-home-lambda ref))
179              (home-kind (functional-kind home)))
180         (unless (or (and (eq home-kind :top-level)
181                          (eq (functional-kind fun) :external))
182                     (eq home-kind :deleted))
183           (res home))))
184     (res)))
185
186 ;;; Move the code for Fun and all functions called by it into Component. If
187 ;;; Fun is already in Component, then we just return that component.
188 ;;;
189 ;;; If the function is in an initial component, then we move its head and
190 ;;; tail to Component and add it to Component's lambdas. It is harmless to
191 ;;; move the tail (even though the return might be unreachable) because if the
192 ;;; return is unreachable it (and its successor link) will be deleted in the
193 ;;; post-deletion pass.
194 ;;;
195 ;;; We then do a Find-DFO-Aux starting at the head of Fun. If this
196 ;;; flow-graph walk encounters another component (which can only happen due to
197 ;;; a non-local exit), then we move code into that component instead. We then
198 ;;; recurse on all functions called from Fun, moving code into whichever
199 ;;; component the preceding call returned.
200 ;;;
201 ;;; If Fun is in the initial component, but the Block-Flag is set in the
202 ;;; bind block, then we just return Component, since we must have already
203 ;;; reached this function in the current walk (or the component would have been
204 ;;; changed).
205 ;;;
206 ;;;    if the function is an XEP, then we also walk all functions that contain
207 ;;; references to the XEP. This is done so that environment analysis doesn't
208 ;;; need to cross component boundaries. This also ensures that conversion of a
209 ;;; full call to a local call won't result in a need to join components, since
210 ;;; the components will already be one.
211 (defun dfo-walk-call-graph (fun component)
212   (declare (type clambda fun) (type component component))
213   (let* ((bind-block (node-block (lambda-bind fun)))
214          (this (block-component bind-block))
215          (return (lambda-return fun)))
216     (cond
217      ((eq this component) component)
218      ((not (eq (component-kind this) :initial))
219       (join-components this component)
220       this)
221      ((block-flag bind-block)
222       component)
223      (t
224       (push fun (component-lambdas component))
225       (setf (component-lambdas this)
226             (delete fun (component-lambdas this)))
227       (link-blocks (component-head component) bind-block)
228       (unlink-blocks (component-head this) bind-block)
229       (when return
230         (let ((return-block (node-block return)))
231           (link-blocks return-block (component-tail component))
232           (unlink-blocks return-block (component-tail this))))
233       (let ((calls (if (eq (functional-kind fun) :external)
234                        (append (find-reference-functions fun)
235                                (lambda-calls fun))
236                        (lambda-calls fun))))
237         (do ((res (find-initial-dfo-aux bind-block component)
238                   (dfo-walk-call-graph (first funs) res))
239              (funs calls (rest funs)))
240             ((null funs) res)
241           (declare (type component res))))))))
242
243 ;;; Return true if Fun is either an XEP or has EXITS to some of its ENTRIES.
244 (defun has-xep-or-nlx (fun)
245   (declare (type clambda fun))
246   (or (eq (functional-kind fun) :external)
247       (let ((entries (lambda-entries fun)))
248         (and entries
249              (find-if #'entry-exits entries)))))
250
251 ;;; Compute the result of FIND-INITIAL-DFO given the list of all resulting
252 ;;; components. Components with a :TOP-LEVEL lambda, but no normal XEPs or
253 ;;; potential non-local exits are marked as :TOP-LEVEL. If there is a
254 ;;; :TOP-LEVEL lambda, and also a normal XEP, then we treat the component as
255 ;;; normal, but also return such components in a list as the third value.
256 ;;; Components with no entry of any sort are deleted.
257 (defun find-top-level-components (components)
258   (declare (list components))
259   (collect ((real)
260             (top)
261             (real-top))
262     (dolist (com components)
263       (unless (eq (block-next (component-head com)) (component-tail com))
264         (let* ((funs (component-lambdas com))
265                (has-top (find :top-level funs :key #'functional-kind)))
266           (cond ((or (find-if #'has-xep-or-nlx funs)
267                      (and has-top (rest funs)))
268                  (setf (component-name com) (find-component-name com))
269                  (real com)
270                  (when has-top
271                    (setf (component-kind com) :complex-top-level)
272                    (real-top com)))
273                 (has-top
274                  (setf (component-kind com) :top-level)
275                  (setf (component-name com) "top-level form")
276                  (top com))
277                 (t
278                  (delete-component com))))))
279
280     (values (real) (top) (real-top))))
281
282 ;;; Given a list of top-level lambdas, return three lists of components
283 ;;; representing the actual component division:
284 ;;;  1. the non-top-level components,
285 ;;;  2. and the second is the top-level components, and
286 ;;;  3. Components in [1] that also have a top-level lambda.
287 ;;;
288 ;;; We assign the DFO for each component, and delete any unreachable blocks.
289 ;;; We assume that the Flags have already been cleared.
290 ;;;
291 ;;; We iterate over the lambdas in each initial component, trying to put
292 ;;; each function in its own component, but joining it to an existing component
293 ;;; if we find that there are references between them. Any code that is left
294 ;;; in an initial component must be unreachable, so we can delete it. Stray
295 ;;; links to the initial component tail (due NIL function terminated blocks)
296 ;;; are moved to the appropriate newc component tail.
297 ;;;
298 ;;; When we are done, we assign DFNs and call FIND-TOP-LEVEL-COMPONENTS to
299 ;;; pull out top-level code.
300 (defun find-initial-dfo (lambdas)
301   (declare (list lambdas))
302   (collect ((components))
303     (let ((new (make-empty-component)))
304       (dolist (tll lambdas)
305         (let ((component (block-component (node-block (lambda-bind tll)))))
306           (dolist (fun (component-lambdas component))
307             (aver (member (functional-kind fun)
308                           '(:optional :external :top-level nil :escape
309                                       :cleanup)))
310             (let ((res (dfo-walk-call-graph fun new)))
311               (when (eq res new)
312                 (components new)
313                 (setq new (make-empty-component)))))
314           (when (eq (component-kind component) :initial)
315             (aver (null (component-lambdas component)))
316             (let ((tail (component-tail component)))
317               (dolist (pred (block-pred tail))
318                 (let ((pred-component (block-component pred)))
319                   (unless (eq pred-component component)
320                     (unlink-blocks pred tail)
321                     (link-blocks pred (component-tail pred-component))))))
322             (delete-component component)))))
323
324     (dolist (com (components))
325       (let ((num 0))
326         (declare (fixnum num))
327         (do-blocks-backwards (block com :both)
328           (setf (block-number block) (incf num)))))
329
330     (find-top-level-components (components))))
331 \f
332 ;;; Insert the code in LAMBDA at the end of RESULT-LAMBDA.
333 (defun merge-1-tl-lambda (result-lambda lambda)
334   (declare (type clambda result-lambda lambda))
335
336   ;; Delete the lambda, and combine the lets and entries.
337   (setf (functional-kind lambda) :deleted)
338   (dolist (let (lambda-lets lambda))
339     (setf (lambda-home let) result-lambda)
340     (setf (lambda-environment let) (lambda-environment result-lambda))
341     (push let (lambda-lets result-lambda)))
342   (setf (lambda-entries result-lambda)
343         (nconc (lambda-entries result-lambda)
344                (lambda-entries lambda)))
345
346   (let* ((bind (lambda-bind lambda))
347          (bind-block (node-block bind))
348          (component (block-component bind-block))
349          (result-component
350           (block-component (node-block (lambda-bind result-lambda))))
351          (result-return-block (node-block (lambda-return result-lambda))))
352
353     ;; Move blocks into the new component, and move any nodes directly in
354     ;; the old lambda into the new one (lets implicitly moved by changing
355     ;; their home.)
356     (do-blocks (block component)
357       (do-nodes (node cont block)
358         (let ((lexenv (node-lexenv node)))
359           (when (eq (lexenv-lambda lexenv) lambda)
360             (setf (lexenv-lambda lexenv) result-lambda))))
361       (setf (block-component block) result-component))
362
363     ;; Splice the blocks into the new DFO, and unlink them from the old
364     ;; component head and tail. Non-return blocks that jump to the tail
365     ;; (NIL returning calls) are switched to go to the new tail.
366     (let* ((head (component-head component))
367            (first (block-next head))
368            (tail (component-tail component))
369            (last (block-prev tail))
370            (prev (block-prev result-return-block)))
371       (setf (block-next prev) first)
372       (setf (block-prev first) prev)
373       (setf (block-next last) result-return-block)
374       (setf (block-prev result-return-block) last)
375       (dolist (succ (block-succ head))
376         (unlink-blocks head succ))
377       (dolist (pred (block-pred tail))
378         (unlink-blocks pred tail)
379         (let ((last (block-last pred)))
380           (unless (return-p last)
381             (aver (basic-combination-p last))
382             (link-blocks pred (component-tail result-component))))))
383
384     (let ((lambdas (component-lambdas component)))
385       (aver (and (null (rest lambdas))
386                  (eq (first lambdas) lambda))))
387
388     ;; Switch the end of the code from the return block to the start of
389     ;; the next chunk.
390     (dolist (pred (block-pred result-return-block))
391       (unlink-blocks pred result-return-block)
392       (link-blocks pred bind-block))
393     (unlink-node bind)
394
395     ;; If there is a return, then delete it (making the preceding node the
396     ;; last node) and link the block to the result return. There is always a
397     ;; preceding REF NIL node in top-level lambdas.
398     (let ((return (lambda-return lambda)))
399       (when return
400         (let ((return-block (node-block return))
401               (result (return-result return)))
402           (setf (block-last return-block) (continuation-use result))
403           (flush-dest result)
404           (delete-continuation result)
405           (link-blocks return-block result-return-block))))))
406
407 ;;; Given a non-empty list of top-level lambdas, smash them into a top-level
408 ;;; lambda and component, returning these as values. We use the first lambda
409 ;;; and its component, putting the other code in that component and deleting
410 ;;; the other lambdas.
411 (defun merge-top-level-lambdas (lambdas)
412   (declare (cons lambdas))
413   (let* ((result-lambda (first lambdas))
414          (result-return (lambda-return result-lambda)))
415     (cond
416      (result-return
417
418       ;; Make sure the result's return node starts a block so that we can
419       ;; splice code in before it.
420       (let ((prev (node-prev
421                    (continuation-use
422                     (return-result result-return)))))
423         (when (continuation-use prev)
424           (node-ends-block (continuation-use prev)))
425         (do-uses (use prev)
426           (let ((new (make-continuation)))
427             (delete-continuation-use use)
428             (add-continuation-use use new))))
429
430       (dolist (lambda (rest lambdas))
431         (merge-1-tl-lambda result-lambda lambda)))
432      (t
433       (dolist (lambda (rest lambdas))
434         (setf (functional-entry-function lambda) nil)
435         (delete-component
436          (block-component
437           (node-block (lambda-bind lambda)))))))
438
439     (values (block-component (node-block (lambda-bind result-lambda)))
440             result-lambda)))