0.8.18.20:
[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-functionals component)))
34   (setf (component-new-functionals component) ())
35   (dolist (clambda (component-lambdas component))
36     (reinit-lambda-physenv clambda))
37   (mapc #'add-lambda-vars-and-let-vars-to-closures
38         (component-lambdas component))
39
40   (find-non-local-exits component)
41   (recheck-dynamic-extent-lvars component)
42   (find-cleanup-points component)
43   (tail-annotate component)
44
45   (dolist (fun (component-lambdas component))
46     (when (null (leaf-refs fun))
47       (let ((kind (functional-kind fun)))
48         (unless (or (eq kind :toplevel)
49                     (functional-has-external-references-p fun))
50           (aver (member kind '(:optional :cleanup :escape)))
51           (setf (functional-kind fun) nil)
52           (delete-functional fun)))))
53
54   (setf (component-nlx-info-generated-p component) t)
55   (values))
56
57 ;;; This is to be called on a COMPONENT with top level LAMBDAs before
58 ;;; the compilation of the associated non-top-level code to detect
59 ;;; closed over top level variables. We just do COMPUTE-CLOSURE on all
60 ;;; the lambdas. This will pre-allocate environments for all the
61 ;;; functions with closed-over top level variables. The post-pass will
62 ;;; use the existing structure, rather than allocating a new one. We
63 ;;; return true if we discover any possible closure vars.
64 (defun pre-physenv-analyze-toplevel (component)
65   (declare (type component component))
66   (let ((found-it nil))
67     (dolist (lambda (component-lambdas component))
68       (when (add-lambda-vars-and-let-vars-to-closures lambda)
69         (setq found-it t)))
70     found-it))
71
72 ;;; This is like old CMU CL PRE-ENVIRONMENT-ANALYZE-TOPLEVEL, except
73 ;;;   (1) It's been brought into the post-0.7.0 world where the property
74 ;;;       HAS-EXTERNAL-REFERENCES-P is orthogonal to the property of
75 ;;;       being specialized/optimized for locall at top level.
76 ;;;   (2) There's no return value, since we don't care whether we
77 ;;;       find any possible closure variables.
78 ;;;
79 ;;; I wish I could find an explanation of why
80 ;;; PRE-ENVIRONMENT-ANALYZE-TOPLEVEL is important. The old CMU CL
81 ;;; comments said
82 ;;;     Called on component with top level lambdas before the
83 ;;;     compilation of the associated non-top-level code to detect
84 ;;;     closed over top level variables. We just do COMPUTE-CLOSURE on
85 ;;;     all the lambdas. This will pre-allocate environments for all
86 ;;;     the functions with closed-over top level variables. The
87 ;;;     post-pass will use the existing structure, rather than
88 ;;;     allocating a new one. We return true if we discover any
89 ;;;     possible closure vars.
90 ;;; But that doesn't seem to explain either why it's important to do
91 ;;; this for top level lambdas, or why it's important to do it only
92 ;;; for top level lambdas instead of just doing it indiscriminately
93 ;;; for all lambdas. I do observe that when it's not done, compiler
94 ;;; assertions occasionally fail. My tentative hypothesis for why it's
95 ;;; important to do it is that other environment analysis expects to
96 ;;; bottom out on the outermost enclosing thing, and (insert
97 ;;; mysterious reason here) it's important to set up bottomed-out-here
98 ;;; environments before anything else. I haven't been able to guess
99 ;;; why it's important to do it selectively instead of
100 ;;; indiscriminately. -- WHN 2001-11-10
101 (defun preallocate-physenvs-for-toplevelish-lambdas (component)
102   (dolist (clambda (component-lambdas component))
103     (when (lambda-toplevelish-p clambda)
104       (add-lambda-vars-and-let-vars-to-closures clambda)))
105   (values))
106
107 ;;; If CLAMBDA has a PHYSENV, return it, otherwise assign an empty one
108 ;;; and return that.
109 (defun get-lambda-physenv (clambda)
110   (declare (type clambda clambda))
111   (let ((homefun (lambda-home clambda)))
112     (or (lambda-physenv homefun)
113         (let ((res (make-physenv :lambda homefun)))
114           (setf (lambda-physenv homefun) res)
115           ;; All the LETLAMBDAs belong to HOMEFUN, and share the same
116           ;; PHYSENV. Thus, (1) since HOMEFUN's PHYSENV was NIL,
117           ;; theirs should be NIL too, and (2) since we're modifying
118           ;; HOMEFUN's PHYSENV, we should modify theirs, too.
119           (dolist (letlambda (lambda-lets homefun))
120             (aver (eql (lambda-home letlambda) homefun))
121             (aver (null (lambda-physenv letlambda)))
122             (setf (lambda-physenv letlambda) res))
123           res))))
124
125 ;;; If FUN has no physical environment, assign one, otherwise clean up
126 ;;; the old physical environment, removing/flagging variables that
127 ;;; have no sets or refs. If a var has no references, we remove it
128 ;;; from the closure. We always clear the INDIRECT flag. This is
129 ;;; necessary because pre-analysis is done before optimization.
130 (defun reinit-lambda-physenv (fun)
131   (let ((old (lambda-physenv (lambda-home fun))))
132     (cond (old
133            (setf (physenv-closure old)
134                  (delete-if (lambda (x)
135                               (and (lambda-var-p x)
136                                    (null (leaf-refs x))))
137                             (physenv-closure old)))
138            (flet ((clear (fun)
139                     (dolist (var (lambda-vars fun))
140                       (setf (lambda-var-indirect var) nil))))
141              (clear fun)
142              (map nil #'clear (lambda-lets fun))))
143           (t
144            (get-lambda-physenv fun))))
145   (values))
146
147 ;;; Get NODE's environment, assigning one if necessary.
148 (defun get-node-physenv (node)
149   (declare (type node node))
150   (get-lambda-physenv (node-home-lambda node)))
151
152 ;;; private guts of ADD-LAMBDA-VARS-AND-LET-VARS-TO-CLOSURES
153 ;;;
154 ;;; This is the old CMU CL COMPUTE-CLOSURE, which only works on
155 ;;; LAMBDA-VARS directly, not on the LAMBDA-VARS of LAMBDA-LETS. It
156 ;;; seems never to be valid to use this operation alone, so in SBCL,
157 ;;; it's private, and the public interface,
158 ;;; ADD-LAMBDA-VARS-AND-LET-VARS-TO-CLOSURES, always runs over all the
159 ;;; variables, not only the LAMBDA-VARS of CLAMBDA itself but also
160 ;;; the LAMBDA-VARS of CLAMBDA's LAMBDA-LETS.
161 (defun %add-lambda-vars-to-closures (clambda)
162   (let ((physenv (get-lambda-physenv clambda))
163         (did-something nil))
164     (note-unreferenced-vars clambda)
165     (dolist (var (lambda-vars clambda))
166       (dolist (ref (leaf-refs var))
167         (let ((ref-physenv (get-node-physenv ref)))
168           (unless (eq ref-physenv physenv)
169             (when (lambda-var-sets var)
170               (setf (lambda-var-indirect var) t))
171             (setq did-something t)
172             (close-over var ref-physenv physenv))))
173       (dolist (set (basic-var-sets var))
174
175         ;; Variables which are set but never referenced can be
176         ;; optimized away, and closing over them here would just
177         ;; interfere with that. (In bug 147, it *did* interfere with
178         ;; that, causing confusion later. This UNLESS solves that
179         ;; problem, but I (WHN) am not 100% sure it's best to solve
180         ;; the problem this way instead of somehow solving it
181         ;; somewhere upstream and just doing (AVER (LEAF-REFS VAR))
182         ;; here.)
183         (unless (null (leaf-refs var))
184
185           (let ((set-physenv (get-node-physenv set)))
186             (unless (eq set-physenv physenv)
187               (setf did-something t
188                     (lambda-var-indirect var) t)
189               (close-over var set-physenv physenv))))))
190     did-something))
191
192 ;;; Find any variables in CLAMBDA -- either directly in LAMBDA-VARS or
193 ;;; in the LAMBDA-VARS of elements of LAMBDA-LETS -- with references
194 ;;; outside of the home environment and close over them. If a
195 ;;; closed-over variable is set, then we set the INDIRECT flag so that
196 ;;; we will know the closed over value is really a pointer to the
197 ;;; value cell. We also warn about unreferenced variables here, just
198 ;;; because it's a convenient place to do it. We return true if we
199 ;;; close over anything.
200 (defun add-lambda-vars-and-let-vars-to-closures (clambda)
201   (declare (type clambda clambda))
202   (let ((did-something nil))
203     (when (%add-lambda-vars-to-closures clambda)
204       (setf did-something t))
205     (dolist (lambda-let (lambda-lets clambda))
206       ;; There's no need to recurse through full COMPUTE-CLOSURE
207       ;; here, since LETS only go one layer deep.
208       (aver (null (lambda-lets lambda-let)))
209       (when (%add-lambda-vars-to-closures lambda-let)
210         (setf did-something t)))
211     did-something))
212
213 (defun xep-allocator (xep)
214   (let ((entry (functional-entry-fun xep)))
215     (functional-allocator entry)))
216
217 ;;; Make sure that THING is closed over in REF-PHYSENV and in all
218 ;;; PHYSENVs for the functions that reference REF-PHYSENV's function
219 ;;; (not just calls). HOME-PHYSENV is THING's home environment. When we
220 ;;; reach the home environment, we stop propagating the closure.
221 (defun close-over (thing ref-physenv home-physenv)
222   (declare (type physenv ref-physenv home-physenv))
223   (let ((flooded-physenvs nil))
224     (labels ((flood (flooded-physenv)
225                (unless (or (eql flooded-physenv home-physenv)
226                            (member flooded-physenv flooded-physenvs))
227                  (push flooded-physenv flooded-physenvs)
228                  (unless (memq thing (physenv-closure flooded-physenv))
229                    (push thing (physenv-closure flooded-physenv))
230                    (let ((lambda (physenv-lambda flooded-physenv)))
231                      (cond ((eq (functional-kind lambda) :external)
232                             (let* ((alloc-node (xep-allocator lambda))
233                                    (alloc-lambda (node-home-lambda alloc-node))
234                                    (alloc-physenv (get-lambda-physenv alloc-lambda)))
235                               (flood alloc-physenv)
236                               (dolist (ref (leaf-refs lambda))
237                                 (close-over lambda
238                                             (get-node-physenv ref) alloc-physenv))))
239                            (t (dolist (ref (leaf-refs lambda))
240                                 ;; FIXME: This assertion looks
241                                 ;; reasonable, but does not work for
242                                 ;; :CLEANUPs.
243                                 #+nil
244                                 (let ((dest (node-dest ref)))
245                                   (aver (basic-combination-p dest))
246                                   (aver (eq (basic-combination-kind dest) :local)))
247                                 (flood (get-node-physenv ref))))))))))
248       (flood ref-physenv)))
249   (values))
250 \f
251 ;;;; non-local exit
252
253 ;;; Insert the entry stub before the original exit target, and add a
254 ;;; new entry to the PHYSENV-NLX-INFO. The %NLX-ENTRY call in the
255 ;;; stub is passed the NLX-INFO as an argument so that the back end
256 ;;; knows what entry is being done.
257 ;;;
258 ;;; The link from the EXIT block to the entry stub is changed to be a
259 ;;; link from the component head. Similarly, the EXIT block is linked
260 ;;; to the component tail. This leaves the entry stub reachable, but
261 ;;; makes the flow graph less confusing to flow analysis.
262 ;;;
263 ;;; If a CATCH or an UNWIND-protect, then we set the LEXENV for the
264 ;;; last node in the cleanup code to be the enclosing environment, to
265 ;;; represent the fact that the binding was undone as a side effect of
266 ;;; the exit. This will cause a lexical exit to be broken up if we are
267 ;;; actually exiting the scope (i.e. a BLOCK), and will also do any
268 ;;; other cleanups that may have to be done on the way.
269 (defun insert-nlx-entry-stub (exit env)
270   (declare (type physenv env) (type exit exit))
271   (let* ((exit-block (node-block exit))
272          (next-block (first (block-succ exit-block)))
273          (entry (exit-entry exit))
274          (cleanup (entry-cleanup entry))
275          (info (make-nlx-info cleanup exit))
276          (new-block (insert-cleanup-code exit-block next-block
277                                          entry
278                                          `(%nlx-entry ',info)
279                                          cleanup))
280          (component (block-component new-block)))
281     (unlink-blocks exit-block new-block)
282     (link-blocks exit-block (component-tail component))
283     (link-blocks (component-head component) new-block)
284
285     (setf (nlx-info-target info) new-block)
286     (push info (physenv-nlx-info env))
287     (push info (cleanup-nlx-info cleanup))
288     (when (member (cleanup-kind cleanup) '(:catch :unwind-protect))
289       (setf (node-lexenv (block-last new-block))
290             (node-lexenv entry))))
291
292   (values))
293
294 ;;; Do stuff necessary to represent a non-local exit from the node
295 ;;; EXIT into ENV. This is called for each non-local exit node, of
296 ;;; which there may be several per exit continuation. This is what we
297 ;;; do:
298 ;;; -- If there isn't any NLX-INFO entry in the environment, make
299 ;;;    an entry stub, otherwise just move the exit block link to
300 ;;;    the component tail.
301 ;;; -- Close over the NLX-INFO in the exit environment.
302 ;;; -- If the exit is from an :ESCAPE function, then substitute a
303 ;;;    constant reference to NLX-INFO structure for the escape
304 ;;;    function reference. This will cause the escape function to
305 ;;;    be deleted (although not removed from the DFO.)  The escape
306 ;;;    function is no longer needed, and we don't want to emit code
307 ;;;    for it.
308 ;;; -- Change the %NLX-ENTRY call to use the NLX lvar so that 1) there
309 ;;;    will be a use to represent the NLX use; 2) make life easier for
310 ;;;    the stack analysis.
311 (defun note-non-local-exit (env exit)
312   (declare (type physenv env) (type exit exit))
313   (let ((lvar (node-lvar exit))
314         (exit-fun (node-home-lambda exit)))
315     (if (find-nlx-info exit)
316         (let ((block (node-block exit)))
317           (aver (= (length (block-succ block)) 1))
318           (unlink-blocks block (first (block-succ block)))
319           (link-blocks block (component-tail (block-component block))))
320         (insert-nlx-entry-stub exit env))
321     (let ((info (find-nlx-info exit)))
322       (aver info)
323       (close-over info (node-physenv exit) env)
324       (when (eq (functional-kind exit-fun) :escape)
325         (mapc (lambda (x)
326                 (setf (node-derived-type x) *wild-type*))
327               (leaf-refs exit-fun))
328         (substitute-leaf (find-constant info) exit-fun))
329       (when lvar
330         (let ((node (block-last (nlx-info-target info))))
331           (unless (node-lvar node)
332             (aver (eq lvar (node-lvar exit)))
333             (setf (node-derived-type node) (lvar-derived-type lvar))
334             (add-lvar-use node lvar))))))
335   (values))
336
337 ;;; Iterate over the EXITs in COMPONENT, calling NOTE-NON-LOCAL-EXIT
338 ;;; when we find a block that ends in a non-local EXIT node. We also
339 ;;; ensure that all EXIT nodes are either non-local or degenerate by
340 ;;; calling IR1-OPTIMIZE-EXIT on local exits. This makes life simpler
341 ;;; for later phases.
342 (defun find-non-local-exits (component)
343   (declare (type component component))
344   (dolist (lambda (component-lambdas component))
345     (dolist (entry (lambda-entries lambda))
346       (dolist (exit (entry-exits entry))
347         (let ((target-physenv (node-physenv entry)))
348           (if (eq (node-physenv exit) target-physenv)
349               (maybe-delete-exit exit)
350               (note-non-local-exit target-physenv exit))))))
351   (values))
352 \f
353 ;;;; final decision on stack allocation of dynamic-extent structures
354 (defun recheck-dynamic-extent-lvars (component)
355   (declare (type component component))
356   (dolist (lambda (component-lambdas component))
357     (loop for entry in (lambda-entries lambda)
358             for cleanup = (entry-cleanup entry)
359             do (when (eq (cleanup-kind cleanup) :dynamic-extent)
360                  (collect ((real-dx-lvars))
361                    (loop for what in (cleanup-info cleanup)
362                          do (etypecase what
363                               (lvar
364                                (let* ((lvar what)
365                                       (use (lvar-uses lvar)))
366                                  (if (and (combination-p use)
367                                           (eq (basic-combination-kind use) :known)
368                                           (awhen (fun-info-stack-allocate-result
369                                                   (basic-combination-fun-info use))
370                                             (funcall it use)))
371                                      (real-dx-lvars lvar)
372                                      (setf (lvar-dynamic-extent lvar) nil))))
373                               (node ; DX closure
374                                (let* ((call what)
375                                       (arg (first (basic-combination-args call)))
376                                       (funs (lvar-value arg))
377                                       (dx nil))
378                                  (dolist (fun funs)
379                                    (binding* ((() (leaf-dynamic-extent fun)
380                                                   :exit-if-null)
381                                               (xep (functional-entry-fun fun)
382                                                    :exit-if-null)
383                                               (closure (physenv-closure
384                                                         (get-lambda-physenv xep))))
385                                      (cond (closure
386                                             (setq dx t))
387                                            (t
388                                             (setf (leaf-dynamic-extent fun) nil)))))
389                                  (when dx
390                                    (setf (lvar-dynamic-extent arg) cleanup)
391                                    (real-dx-lvars arg))))))
392                    (setf (cleanup-info cleanup) (real-dx-lvars))
393                    (setf (component-dx-lvars component)
394                          (append (real-dx-lvars) (component-dx-lvars component)))))))
395   (values))
396 \f
397 ;;;; cleanup emission
398
399 ;;; Zoom up the cleanup nesting until we hit CLEANUP1, accumulating
400 ;;; cleanup code as we go. When we are done, convert the cleanup code
401 ;;; in an implicit MV-PROG1. We have to force local call analysis of
402 ;;; new references to UNWIND-PROTECT cleanup functions. If we don't
403 ;;; actually have to do anything, then we don't insert any cleanup
404 ;;; code. (FIXME: There's some confusion here, left over from CMU CL
405 ;;; comments. CLEANUP1 isn't mentioned in the code of this function.
406 ;;; It is in code elsewhere, but if the comments for this function
407 ;;; mention it they should explain the relationship to the other code.)
408 ;;;
409 ;;; If we do insert cleanup code, we check that BLOCK1 doesn't end in
410 ;;; a "tail" local call.
411 ;;;
412 ;;; We don't need to adjust the ending cleanup of the cleanup block,
413 ;;; since the cleanup blocks are inserted at the start of the DFO, and
414 ;;; are thus never scanned.
415 (defun emit-cleanups (block1 block2)
416   (declare (type cblock block1 block2))
417   (collect ((code)
418             (reanalyze-funs))
419     (let ((cleanup2 (block-start-cleanup block2)))
420       (do ((cleanup (block-end-cleanup block1)
421                     (node-enclosing-cleanup (cleanup-mess-up cleanup))))
422           ((eq cleanup cleanup2))
423         (let* ((node (cleanup-mess-up cleanup))
424                (args (when (basic-combination-p node)
425                        (basic-combination-args node))))
426           (ecase (cleanup-kind cleanup)
427             (:special-bind
428              (code `(%special-unbind ',(lvar-value (first args)))))
429             (:catch
430              (code `(%catch-breakup)))
431             (:unwind-protect
432              (code `(%unwind-protect-breakup))
433              (let ((fun (ref-leaf (lvar-uses (second args)))))
434                (reanalyze-funs fun)
435                (code `(%funcall ,fun))))
436             ((:block :tagbody)
437              (dolist (nlx (cleanup-nlx-info cleanup))
438                (code `(%lexical-exit-breakup ',nlx))))
439             (:dynamic-extent
440              (when (not (null (cleanup-info cleanup)))
441                (code `(%cleanup-point)))))))
442
443       (when (code)
444         (aver (not (node-tail-p (block-last block1))))
445         (insert-cleanup-code block1 block2
446                              (block-last block1)
447                              `(progn ,@(code)))
448         (dolist (fun (reanalyze-funs))
449           (locall-analyze-fun-1 fun)))))
450
451   (values))
452
453 ;;; Loop over the blocks in COMPONENT, calling EMIT-CLEANUPS when we
454 ;;; see a successor in the same environment with a different cleanup.
455 ;;; We ignore the cleanup transition if it is to a cleanup enclosed by
456 ;;; the current cleanup, since in that case we are just messing up the
457 ;;; environment, hence this is not the place to clean it.
458 (defun find-cleanup-points (component)
459   (declare (type component component))
460   (do-blocks (block1 component)
461     (let ((env1 (block-physenv block1))
462           (cleanup1 (block-end-cleanup block1)))
463       (dolist (block2 (block-succ block1))
464         (when (block-start block2)
465           (let ((env2 (block-physenv block2))
466                 (cleanup2 (block-start-cleanup block2)))
467             (unless (or (not (eq env2 env1))
468                         (eq cleanup1 cleanup2)
469                         (and cleanup2
470                              (eq (node-enclosing-cleanup
471                                   (cleanup-mess-up cleanup2))
472                                  cleanup1)))
473               (emit-cleanups block1 block2)))))))
474   (values))
475
476 ;;; Mark optimizable tail-recursive uses of function result
477 ;;; continuations with the corresponding TAIL-SET.
478 (defun tail-annotate (component)
479   (declare (type component component))
480   (dolist (fun (component-lambdas component))
481     (let ((ret (lambda-return fun)))
482       ;; Nodes whose type is NIL (i.e. don't return) such as calls to
483       ;; ERROR are never annotated as TAIL-P, in order to preserve
484       ;; debugging information.
485       ;;
486       ;; FIXME: It might be better to add another DEFKNOWN property
487       ;; (e.g. NO-TAIL-RECURSION) and use it for error-handling
488       ;; functions like ERROR, instead of spreading this special case
489       ;; net so widely.
490       (when ret
491         (let ((result (return-result ret)))
492           (do-uses (use result)
493             (when (and (policy use merge-tail-calls)
494                        (basic-combination-p use)
495                        (immediately-used-p result use)
496                        (or (not (eq (node-derived-type use) *empty-type*))
497                            (eq (basic-combination-kind use) :local)))
498               (setf (node-tail-p use) t)))))))
499   (values))