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