4afe914d7f241e90333514f2bb7893eaf2038da5
[sbcl.git] / src / compiler / physenvanal.lisp
1 ;;;; This file implements the environment analysis phase for the
2 ;;;; compiler. This phase annotates IR1 with a hierarchy environment
3 ;;;; structures, determining the physical environment that each LAMBDA
4 ;;;; allocates its variables and finding what values are closed over
5 ;;;; by each physical environment.
6
7 ;;;; This software is part of the SBCL system. See the README file for
8 ;;;; more information.
9 ;;;;
10 ;;;; This software is derived from the CMU CL system, which was
11 ;;;; written at Carnegie Mellon University and released into the
12 ;;;; public domain. The software is in the public domain and is
13 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
14 ;;;; files for more information.
15
16 (in-package "SB!C")
17
18 ;;; Do environment analysis on the code in COMPONENT. This involves
19 ;;; various things:
20 ;;;  1. Make a PHYSENV structure for each non-LET LAMBDA, assigning 
21 ;;;     the LAMBDA-PHYSENV for all LAMBDAs.
22 ;;;  2. Find all values that need to be closed over by each
23 ;;;     physical environment.
24 ;;;  3. Scan the blocks in the component closing over non-local-exit
25 ;;;     continuations.
26 ;;;  4. Delete all non-top-level functions with no references. This
27 ;;;     should only get functions with non-NULL kinds, since normal
28 ;;;     functions are deleted when their references go to zero. 
29 (defun physenv-analyze (component)
30   (declare (type component component))
31   (aver (every (lambda (x)
32                  (eq (functional-kind x) :deleted))
33                (component-new-funs component)))
34   (setf (component-new-funs component) ())
35   (dolist (fun (component-lambdas component))
36     (reinit-lambda-physenv fun))
37   (mapc #'compute-closure (component-lambdas component))
38
39   (find-non-local-exits component)
40   (find-cleanup-points component)
41   (tail-annotate component)
42
43   (dolist (fun (component-lambdas component))
44     (when (null (leaf-refs fun))
45       (let ((kind (functional-kind fun)))
46         (unless (or (eq kind :toplevel)
47                     (functional-has-external-references-p fun))
48           (aver (member kind '(:optional :cleanup :escape)))
49           (setf (functional-kind fun) nil)
50           (delete-functional fun)))))
51
52   (values))
53
54 ;;; This is to be called on a COMPONENT with top level LAMBDAs before
55 ;;; the compilation of the associated non-top-level code to detect
56 ;;; closed over top level variables. We just do COMPUTE-CLOSURE on all
57 ;;; the lambdas. This will pre-allocate environments for all the
58 ;;; functions with closed-over top level variables. The post-pass will
59 ;;; use the existing structure, rather than allocating a new one. We
60 ;;; return true if we discover any possible closure vars.
61 (defun pre-physenv-analyze-toplevel (component)
62   (declare (type component component))
63   (let ((found-it nil))
64     (dolist (lambda (component-lambdas component))
65       (when (compute-closure lambda)
66         (setq found-it t)))
67     found-it))
68
69 ;;; This is like old CMU CL PRE-ENVIRONMENT-ANALYZE-TOPLEVEL, except
70 ;;;   (1) It's been brought into the post-0.7.0 world where the property
71 ;;;       HAS-EXTERNAL-REFERENCES-P is orthogonal to the property of
72 ;;;       being specialized/optimized for locall at top level.
73 ;;;   (2) There's no return value, since we don't care whether we
74 ;;;       find any possible closure variables.
75 ;;;
76 ;;; I wish I could find an explanation of why
77 ;;; PRE-ENVIRONMENT-ANALYZE-TOPLEVEL is important. The old CMU CL
78 ;;; comments said
79 ;;;     Called on component with top level lambdas before the
80 ;;;     compilation of the associated non-top-level code to detect
81 ;;;     closed over top level variables. We just do COMPUTE-CLOSURE on
82 ;;;     all the lambdas. This will pre-allocate environments for all
83 ;;;     the functions with closed-over top level variables. The
84 ;;;     post-pass will use the existing structure, rather than
85 ;;;     allocating a new one. We return true if we discover any
86 ;;;     possible closure vars.
87 ;;; But that doesn't seem to explain either why it's important to do
88 ;;; this for top level lambdas, or why it's important to do it only
89 ;;; for top level lambdas instead of just doing it indiscriminately
90 ;;; for all lambdas. I do observe that when it's not done, compiler
91 ;;; assertions occasionally fail. My tentative hypothesis for why it's
92 ;;; important to do it is that other environment analysis expects to
93 ;;; bottom out on the outermost enclosing thing, and (insert
94 ;;; mysterious reason here) it's important to set up bottomed-out-here
95 ;;; environments before anything else. I haven't been able to guess
96 ;;; why it's important to do it selectively instead of
97 ;;; indiscriminately. -- WHN 2001-11-10
98 (defun preallocate-physenvs-for-toplevelish-lambdas (component)
99   (dolist (clambda (component-lambdas component))
100     (when (lambda-toplevelish-p clambda)
101       (compute-closure clambda)))
102   (values))
103
104 ;;; If CLAMBDA has a PHYSENV, return it, otherwise assign an empty one
105 ;;; and return that.
106 (defun get-lambda-physenv (clambda)
107   (declare (type clambda clambda))
108   (let ((homefun (lambda-home clambda)))
109     (or (lambda-physenv homefun)
110         (let ((res (make-physenv :lambda homefun)))
111           (setf (lambda-physenv homefun) res)
112           ;; All the LETLAMBDAs belong to HOMEFUN, and share the same
113           ;; PHYSENV. Thus, (1) since HOMEFUN's PHYSENV was NIL,
114           ;; theirs should be NIL too, and (2) since we're modifying
115           ;; HOMEFUN's PHYSENV, we should modify theirs, too.
116           (dolist (letlambda (lambda-lets homefun))
117             (aver (eql (lambda-home letlambda) homefun))
118             (aver (null (lambda-physenv letlambda)))
119             (setf (lambda-physenv letlambda) res))
120           res))))
121
122 ;;; If FUN has no physical environment, assign one, otherwise clean up
123 ;;; the old physical environment, removing/flagging variables that
124 ;;; have no sets or refs. If a var has no references, we remove it
125 ;;; from the closure. If it has no sets, we clear the INDIRECT flag.
126 ;;; This is necessary because pre-analysis is done before
127 ;;; optimization.
128 (defun reinit-lambda-physenv (fun)
129   (let ((old (lambda-physenv (lambda-home fun))))
130     (cond (old
131            (setf (physenv-closure old)
132                  (delete-if (lambda (x)
133                               (and (lambda-var-p x)
134                                    (null (leaf-refs x))))
135                             (physenv-closure old)))
136            (flet ((clear (fun)
137                     (dolist (var (lambda-vars fun))
138                       (unless (lambda-var-sets var)
139                         (setf (lambda-var-indirect var) nil)))))
140              (clear fun)
141              (map nil #'clear (lambda-lets fun))))
142           (t
143            (get-lambda-physenv fun))))
144   (values))
145
146 ;;; Get NODE's environment, assigning one if necessary.
147 (defun get-node-physenv (node)
148   (declare (type node node))
149   (get-lambda-physenv (node-home-lambda node)))
150
151 ;;; Find any variables in CLAMBDA -- either directly in LAMBDA-VARS or
152 ;;; in the LAMBDA-VARS of elements of LAMBDA-LETS -- with references
153 ;;; outside of the home environment and close over them. If a
154 ;;; closed-over variable is set, then we set the INDIRECT flag so that
155 ;;; we will know the closed over value is really a pointer to the
156 ;;; value cell. We also warn about unreferenced variables here, just
157 ;;; because it's a convenient place to do it. We return true if we
158 ;;; close over anything.
159 (defun compute-closure (clambda)
160   (declare (type clambda clambda))
161   (flet (;; This is the old CMU CL COMPUTE-CLOSURE, which only works
162          ;; on LAMBDA-VARS directly, not on the LAMBDA-VARS of
163          ;; LAMBDA-LETS. It seems never to be valid to use this
164          ;; operation alone, so in SBCL, it's private, and the public
165          ;; interface always runs over all the variables, both the
166          ;; LAMBDA-VARS of CLAMBDA itself and the LAMBDA-VARS of
167          ;; CLAMBDA's LAMBDA-LETS.
168          ;;
169          ;; Note that we don't need to make a distinction between the
170          ;; outer CLAMBDA argument and the inner one, or refer to the
171          ;; outer CLAMBDA argument at all, because the LET-conversion
172          ;; process carefully modifies all the necessary CLAMBDA slots
173          ;; (e.g. LAMBDA-PHYSENV) of a LET-converted CLAMBDA to refer
174          ;; to the new home.
175          (%compute-closure (clambda)
176            (let ((physenv (get-lambda-physenv clambda))
177                  (did-something nil))
178              (note-unreferenced-vars clambda)
179              (dolist (var (lambda-vars clambda))
180                (dolist (ref (leaf-refs var))
181                  (let ((ref-physenv (get-node-physenv ref)))
182                    (unless (eq ref-physenv physenv)
183                      (when (lambda-var-sets var)
184                        (setf (lambda-var-indirect var) t))
185                      (setq did-something t)
186                      (close-over var ref-physenv physenv))))
187                (dolist (set (basic-var-sets var))
188                  (let ((set-physenv (get-node-physenv set)))
189                    (unless (eq set-physenv physenv)
190                      (setq did-something t)
191                      (setf (lambda-var-indirect var) t)
192                      (close-over var set-physenv physenv)))))
193              did-something)))
194     (let ((did-something nil))
195       (when (%compute-closure clambda)
196         (setf did-something t))
197       (dolist (lambda-let (lambda-lets clambda))
198         ;; There's no need to recurse through full COMPUTE-CLOSURE
199         ;; here, since LETS only go one layer deep.
200         (aver (null (lambda-lets lambda-let)))
201         (when (%compute-closure lambda-let)
202           (setf did-something t)))
203       did-something)))
204
205 ;;; Make sure that THING is closed over in REF-PHYSENV and in all
206 ;;; PHYSENVs for the functions that reference REF-PHYSENV's function
207 ;;; (not just calls). HOME-PHYSENV is THING's home environment. When we
208 ;;; reach the home environment, we stop propagating the closure.
209 (defun close-over (thing ref-physenv home-physenv)
210   (declare (type physenv ref-physenv home-physenv))
211   (cond ((eq ref-physenv home-physenv))
212         ((member thing (physenv-closure ref-physenv)))
213         (t
214          (push thing (physenv-closure ref-physenv))
215          (dolist (call (leaf-refs (physenv-lambda ref-physenv)))
216            (close-over thing (get-node-physenv call) home-physenv))))
217   (values))
218 \f
219 ;;;; non-local exit
220
221 ;;; Insert the entry stub before the original exit target, and add a
222 ;;; new entry to the PHYSENV-NLX-INFO. The %NLX-ENTRY call in the
223 ;;; stub is passed the NLX-INFO as an argument so that the back end
224 ;;; knows what entry is being done.
225 ;;;
226 ;;; The link from the EXIT block to the entry stub is changed to be a
227 ;;; link to the component head. Similarly, the EXIT block is linked to
228 ;;; the component tail. This leaves the entry stub reachable, but
229 ;;; makes the flow graph less confusing to flow analysis.
230 ;;;
231 ;;; If a CATCH or an UNWIND-protect, then we set the LEXENV for the
232 ;;; last node in the cleanup code to be the enclosing environment, to
233 ;;; represent the fact that the binding was undone as a side-effect of
234 ;;; the exit. This will cause a lexical exit to be broken up if we are
235 ;;; actually exiting the scope (i.e. a BLOCK), and will also do any
236 ;;; other cleanups that may have to be done on the way.
237 (defun insert-nlx-entry-stub (exit env)
238   (declare (type physenv env) (type exit exit))
239   (let* ((exit-block (node-block exit))
240          (next-block (first (block-succ exit-block)))
241          (cleanup (entry-cleanup (exit-entry exit)))
242          (info (make-nlx-info :cleanup cleanup
243                               :continuation (node-cont exit)))
244          (entry (exit-entry exit))
245          (new-block (insert-cleanup-code exit-block next-block
246                                          entry
247                                          `(%nlx-entry ',info)
248                                          (entry-cleanup entry)))
249          (component (block-component new-block)))
250     (unlink-blocks exit-block new-block)
251     (link-blocks exit-block (component-tail component))
252     (link-blocks (component-head component) new-block)
253
254     (setf (nlx-info-target info) new-block)
255     (push info (physenv-nlx-info env))
256     (push info (cleanup-nlx-info cleanup))
257     (when (member (cleanup-kind cleanup) '(:catch :unwind-protect))
258       (setf (node-lexenv (block-last new-block))
259             (node-lexenv entry))))
260
261   (values))
262
263 ;;; Do stuff necessary to represent a non-local exit from the node
264 ;;; EXIT into ENV. This is called for each non-local exit node, of
265 ;;; which there may be several per exit continuation. This is what we
266 ;;; do:
267 ;;; -- If there isn't any NLX-Info entry in the environment, make
268 ;;;    an entry stub, otherwise just move the exit block link to
269 ;;;    the component tail.
270 ;;; -- Close over the NLX-Info in the exit environment.
271 ;;; -- If the exit is from an :Escape function, then substitute a
272 ;;;    constant reference to NLX-Info structure for the escape
273 ;;;    function reference. This will cause the escape function to
274 ;;;    be deleted (although not removed from the DFO.)  The escape
275 ;;;    function is no longer needed, and we don't want to emit code
276 ;;;    for it. We then also change the %NLX-ENTRY call to use the
277 ;;;    NLX continuation so that there will be a use to represent
278 ;;;    the NLX use.
279 (defun note-non-local-exit (env exit)
280   (declare (type physenv env) (type exit exit))
281   (let ((entry (exit-entry exit))
282         (cont (node-cont exit))
283         (exit-fun (node-home-lambda exit)))
284
285     (if (find-nlx-info entry cont)
286         (let ((block (node-block exit)))
287           (aver (= (length (block-succ block)) 1))
288           (unlink-blocks block (first (block-succ block)))
289           (link-blocks block (component-tail (block-component block))))
290         (insert-nlx-entry-stub exit env))
291
292     (let ((info (find-nlx-info entry cont)))
293       (aver info)
294       (close-over info (node-physenv exit) env)
295       (when (eq (functional-kind exit-fun) :escape)
296         (mapc #'(lambda (x)
297                   (setf (node-derived-type x) *wild-type*))
298               (leaf-refs exit-fun))
299         (substitute-leaf (find-constant info) exit-fun)
300         (let ((node (block-last (nlx-info-target info))))
301           (delete-continuation-use node)
302           (add-continuation-use node (nlx-info-continuation info))))))
303
304   (values))
305
306 ;;; Iterate over the EXITs in COMPONENT, calling NOTE-NON-LOCAL-EXIT
307 ;;; when we find a block that ends in a non-local EXIT node. We also
308 ;;; ensure that all EXIT nodes are either non-local or degenerate by
309 ;;; calling IR1-OPTIMIZE-EXIT on local exits. This makes life simpler
310 ;;; for later phases.
311 (defun find-non-local-exits (component)
312   (declare (type component component))
313   (dolist (lambda (component-lambdas component))
314     (dolist (entry (lambda-entries lambda))
315       (dolist (exit (entry-exits entry))
316         (let ((target-env (node-physenv entry)))
317           (if (eq (node-physenv exit) target-env)
318               (maybe-delete-exit exit)
319               (note-non-local-exit target-env exit))))))
320
321   (values))
322 \f
323 ;;;; cleanup emission
324
325 ;;; Zoom up the cleanup nesting until we hit CLEANUP1, accumulating
326 ;;; cleanup code as we go. When we are done, convert the cleanup code
327 ;;; in an implicit MV-PROG1. We have to force local call analysis of
328 ;;; new references to UNWIND-PROTECT cleanup functions. If we don't
329 ;;; actually have to do anything, then we don't insert any cleanup
330 ;;; code.
331 ;;;
332 ;;; If we do insert cleanup code, we check that BLOCK1 doesn't end in
333 ;;; a "tail" local call.
334 ;;;
335 ;;; We don't need to adjust the ending cleanup of the cleanup block,
336 ;;; since the cleanup blocks are inserted at the start of the DFO, and
337 ;;; are thus never scanned.
338 (defun emit-cleanups (block1 block2)
339   (declare (type cblock block1 block2))
340   (collect ((code)
341             (reanalyze-funs))
342     (let ((cleanup2 (block-start-cleanup block2)))
343       (do ((cleanup (block-end-cleanup block1)
344                     (node-enclosing-cleanup (cleanup-mess-up cleanup))))
345           ((eq cleanup cleanup2))
346         (let* ((node (cleanup-mess-up cleanup))
347                (args (when (basic-combination-p node)
348                        (basic-combination-args node))))
349           (ecase (cleanup-kind cleanup)
350             (:special-bind
351              (code `(%special-unbind ',(continuation-value (first args)))))
352             (:catch
353              (code `(%catch-breakup)))
354             (:unwind-protect
355              (code `(%unwind-protect-breakup))
356              (let ((fun (ref-leaf (continuation-use (second args)))))
357                (reanalyze-funs fun)
358                (code `(%funcall ,fun))))
359             ((:block :tagbody)
360              (dolist (nlx (cleanup-nlx-info cleanup))
361                (code `(%lexical-exit-breakup ',nlx)))))))
362
363       (when (code)
364         (aver (not (node-tail-p (block-last block1))))
365         (insert-cleanup-code block1 block2
366                              (block-last block1)
367                              `(progn ,@(code)))
368         (dolist (fun (reanalyze-funs))
369           (locall-analyze-fun-1 fun)))))
370
371   (values))
372
373 ;;; Loop over the blocks in COMPONENT, calling EMIT-CLEANUPS when we
374 ;;; see a successor in the same environment with a different cleanup.
375 ;;; We ignore the cleanup transition if it is to a cleanup enclosed by
376 ;;; the current cleanup, since in that case we are just messing up the
377 ;;; environment, hence this is not the place to clean it.
378 (defun find-cleanup-points (component)
379   (declare (type component component))
380   (do-blocks (block1 component)
381     (let ((env1 (block-physenv block1))
382           (cleanup1 (block-end-cleanup block1)))
383       (dolist (block2 (block-succ block1))
384         (when (block-start block2)
385           (let ((env2 (block-physenv block2))
386                 (cleanup2 (block-start-cleanup block2)))
387             (unless (or (not (eq env2 env1))
388                         (eq cleanup1 cleanup2)
389                         (and cleanup2
390                              (eq (node-enclosing-cleanup
391                                   (cleanup-mess-up cleanup2))
392                                  cleanup1)))
393               (emit-cleanups block1 block2)))))))
394   (values))
395
396 ;;; Mark all tail-recursive uses of function result continuations with
397 ;;; the corresponding TAIL-SET. Nodes whose type is NIL (i.e. don't
398 ;;; return) such as calls to ERROR are never annotated as tail in
399 ;;; order to preserve debugging information.
400 (defun tail-annotate (component)
401   (declare (type component component))
402   (dolist (fun (component-lambdas component))
403     (let ((ret (lambda-return fun)))
404       (when ret
405         (let ((result (return-result ret)))
406           (do-uses (use result)
407             (when (and (immediately-used-p result use)
408                      (or (not (eq (node-derived-type use) *empty-type*))
409                          (not (basic-combination-p use))
410                          (eq (basic-combination-kind use) :local)))
411                 (setf (node-tail-p use) t)))))))
412   (values))