1 ;;;; This file contains miscellaneous utilities used for manipulating
2 ;;;; the IR1 representation.
4 ;;;; This software is part of the SBCL system. See the README file for
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.
17 ;;; Return the innermost cleanup enclosing NODE, or NIL if there is
18 ;;; none in its function. If NODE has no cleanup, but is in a LET,
19 ;;; then we must still check the environment that the call is in.
20 (defun node-enclosing-cleanup (node)
21 (declare (type node node))
22 (do ((lexenv (node-lexenv node)
23 (lambda-call-lexenv (lexenv-lambda lexenv))))
25 (let ((cup (lexenv-cleanup lexenv)))
26 (when cup (return cup)))))
28 ;;; Convert the FORM in a block inserted between BLOCK1 and BLOCK2 as
29 ;;; an implicit MV-PROG1. The inserted block is returned. NODE is used
30 ;;; for IR1 context when converting the form. Note that the block is
31 ;;; not assigned a number, and is linked into the DFO at the
32 ;;; beginning. We indicate that we have trashed the DFO by setting
33 ;;; COMPONENT-REANALYZE. If CLEANUP is supplied, then convert with
35 (defun insert-cleanup-code (block1 block2 node form &optional cleanup)
36 (declare (type cblock block1 block2) (type node node)
37 (type (or cleanup null) cleanup))
38 (setf (component-reanalyze (block-component block1)) t)
39 (with-ir1-environment-from-node node
40 (let* ((start (make-continuation))
41 (block (continuation-starts-block start))
42 (cont (make-continuation))
44 (make-lexenv :cleanup cleanup)
46 (change-block-successor block1 block2 block)
47 (link-blocks block block2)
48 (ir1-convert start cont form)
49 (setf (block-last block) (continuation-use cont))
52 ;;;; continuation use hacking
54 ;;; Return a list of all the nodes which use Cont.
55 (declaim (ftype (function (continuation) list) find-uses))
56 (defun find-uses (cont)
57 (ecase (continuation-kind cont)
58 ((:block-start :deleted-block-start)
59 (block-start-uses (continuation-block cont)))
60 (:inside-block (list (continuation-use cont)))
64 ;;; Update continuation use information so that NODE is no longer a
65 ;;; use of its CONT. If the old continuation doesn't start its block,
66 ;;; then we don't update the BLOCK-START-USES, since it will be
67 ;;; deleted when we are done.
69 ;;; Note: if you call this function, you may have to do a
70 ;;; REOPTIMIZE-CONTINUATION to inform IR1 optimization that something
72 (declaim (ftype (function (node) (values)) delete-continuation-use))
73 (defun delete-continuation-use (node)
74 (let* ((cont (node-cont node))
75 (block (continuation-block cont)))
76 (ecase (continuation-kind cont)
78 ((:block-start :deleted-block-start)
79 (let ((uses (delete node (block-start-uses block))))
80 (setf (block-start-uses block) uses)
81 (setf (continuation-use cont)
82 (if (cdr uses) nil (car uses)))))
84 (setf (continuation-kind cont) :unused)
85 (setf (continuation-block cont) nil)
86 (setf (continuation-use cont) nil)
87 (setf (continuation-next cont) nil)))
88 (setf (node-cont node) nil))
91 ;;; Update continuation use information so that NODE uses CONT. If
92 ;;; CONT is :UNUSED, then we set its block to NODE's NODE-BLOCK (which
95 ;;; Note: if you call this function, you may have to do a
96 ;;; REOPTIMIZE-CONTINUATION to inform IR1 optimization that something
98 (declaim (ftype (function (node continuation) (values)) add-continuation-use))
99 (defun add-continuation-use (node cont)
100 (aver (not (node-cont node)))
101 (let ((block (continuation-block cont)))
102 (ecase (continuation-kind cont)
106 (let ((block (node-block node)))
108 (setf (continuation-block cont) block))
109 (setf (continuation-kind cont) :inside-block)
110 (setf (continuation-use cont) node))
111 ((:block-start :deleted-block-start)
112 (let ((uses (cons node (block-start-uses block))))
113 (setf (block-start-uses block) uses)
114 (setf (continuation-use cont)
115 (if (cdr uses) nil (car uses)))))))
116 (setf (node-cont node) cont)
119 ;;; Return true if CONT is the NODE-CONT for NODE and CONT is
120 ;;; transferred to immediately after the evaluation of NODE.
121 (defun immediately-used-p (cont node)
122 (declare (type continuation cont) (type node node))
123 (and (eq (node-cont node) cont)
124 (not (eq (continuation-kind cont) :deleted))
125 (let ((cblock (continuation-block cont))
126 (nblock (node-block node)))
127 (or (eq cblock nblock)
128 (let ((succ (block-succ nblock)))
129 (and (= (length succ) 1)
130 (eq (first succ) cblock)))))))
132 ;;;; continuation substitution
134 ;;; In OLD's DEST, replace OLD with NEW. NEW's DEST must initially be
135 ;;; NIL. When we are done, we call FLUSH-DEST on OLD to clear its DEST
136 ;;; and to note potential optimization opportunities.
137 (defun substitute-continuation (new old)
138 (declare (type continuation old new))
139 (aver (not (continuation-dest new)))
140 (let ((dest (continuation-dest old)))
143 (cif (setf (if-test dest) new))
144 (cset (setf (set-value dest) new))
145 (creturn (setf (return-result dest) new))
146 (exit (setf (exit-value dest) new))
148 (if (eq old (basic-combination-fun dest))
149 (setf (basic-combination-fun dest) new)
150 (setf (basic-combination-args dest)
151 (nsubst new old (basic-combination-args dest))))))
154 (setf (continuation-dest new) dest)
155 (setf (continuation-%externally-checkable-type new) nil))
158 ;;; Replace all uses of OLD with uses of NEW, where NEW has an
159 ;;; arbitary number of uses. If NEW will end up with more than one
160 ;;; use, then we must arrange for it to start a block if it doesn't
162 (defun substitute-continuation-uses (new old)
163 (declare (type continuation old new))
164 (unless (and (eq (continuation-kind new) :unused)
165 (eq (continuation-kind old) :inside-block))
166 (ensure-block-start new))
169 (delete-continuation-use node)
170 (add-continuation-use node new))
171 (dolist (lexenv-use (continuation-lexenv-uses old))
172 (setf (cadr lexenv-use) new))
174 (reoptimize-continuation new)
177 ;;;; block starting/creation
179 ;;; Return the block that CONT is the start of, making a block if
180 ;;; necessary. This function is called by IR1 translators which may
181 ;;; cause a continuation to be used more than once. Every continuation
182 ;;; which may be used more than once must start a block by the time
183 ;;; that anyone does a USE-CONTINUATION on it.
185 ;;; We also throw the block into the next/prev list for the
186 ;;; *CURRENT-COMPONENT* so that we keep track of which blocks we have
188 (defun continuation-starts-block (cont)
189 (declare (type continuation cont))
190 (ecase (continuation-kind cont)
192 (aver (not (continuation-block cont)))
193 (let* ((head (component-head *current-component*))
194 (next (block-next head))
195 (new-block (make-block cont)))
196 (setf (block-next new-block) next
197 (block-prev new-block) head
198 (block-prev next) new-block
199 (block-next head) new-block
200 (continuation-block cont) new-block
201 (continuation-use cont) nil
202 (continuation-kind cont) :block-start)
205 (continuation-block cont))))
207 ;;; Ensure that CONT is the start of a block (or deleted) so that
208 ;;; the use set can be freely manipulated.
209 ;;; -- If the continuation is :UNUSED or is :INSIDE-BLOCK and the
210 ;;; CONT of LAST in its block, then we make it the start of a new
212 ;;; -- If the continuation is :INSIDE-BLOCK inside a block, then we
213 ;;; split the block using NODE-ENDS-BLOCK, which makes the
214 ;;; continuation be a :BLOCK-START.
215 (defun ensure-block-start (cont)
216 (declare (type continuation cont))
217 (let ((kind (continuation-kind cont)))
219 ((:deleted :block-start :deleted-block-start))
220 ((:unused :inside-block)
221 (let ((block (continuation-block cont)))
222 (cond ((or (eq kind :unused)
223 (eq (node-cont (block-last block)) cont))
224 (setf (continuation-block cont)
225 (make-block-key :start cont
227 :start-uses (find-uses cont)))
228 (setf (continuation-kind cont) :deleted-block-start))
230 (node-ends-block (continuation-use cont))))))))
233 ;;;; miscellaneous shorthand functions
235 ;;; Return the home (i.e. enclosing non-LET) CLAMBDA for NODE. Since
236 ;;; the LEXENV-LAMBDA may be deleted, we must chain up the
237 ;;; LAMBDA-CALL-LEXENV thread until we find a CLAMBDA that isn't
238 ;;; deleted, and then return its home.
239 (defun node-home-lambda (node)
240 (declare (type node node))
241 (do ((fun (lexenv-lambda (node-lexenv node))
242 (lexenv-lambda (lambda-call-lexenv fun))))
243 ((not (eq (functional-kind fun) :deleted))
245 (when (eq (lambda-home fun) fun)
248 (defun node-block (node)
249 (declare (type node node))
250 (the cblock (continuation-block (node-prev node))))
251 (defun node-component (node)
252 (declare (type node node))
253 (block-component (node-block node)))
254 (defun node-physenv (node)
255 (declare (type node node))
256 (the physenv (lambda-physenv (node-home-lambda node))))
258 (defun lambda-block (clambda)
259 (declare (type clambda clambda))
260 (node-block (lambda-bind clambda)))
261 (defun lambda-component (clambda)
262 (block-component (lambda-block clambda)))
264 ;;; Return the enclosing cleanup for environment of the first or last
266 (defun block-start-cleanup (block)
267 (declare (type cblock block))
268 (node-enclosing-cleanup (continuation-next (block-start block))))
269 (defun block-end-cleanup (block)
270 (declare (type cblock block))
271 (node-enclosing-cleanup (block-last block)))
273 ;;; Return the non-LET LAMBDA that holds BLOCK's code, or NIL
274 ;;; if there is none.
276 ;;; There can legitimately be no home lambda in dead code early in the
277 ;;; IR1 conversion process, e.g. when IR1-converting the SETQ form in
278 ;;; (BLOCK B (RETURN-FROM B) (SETQ X 3))
279 ;;; where the block is just a placeholder during parsing and doesn't
280 ;;; actually correspond to code which will be written anywhere.
281 (defun block-home-lambda-or-null (block)
282 (declare (type cblock block))
283 (if (node-p (block-last block))
284 ;; This is the old CMU CL way of doing it.
285 (node-home-lambda (block-last block))
286 ;; Now that SBCL uses this operation more aggressively than CMU
287 ;; CL did, the old CMU CL way of doing it can fail in two ways.
288 ;; 1. It can fail in a few cases even when a meaningful home
289 ;; lambda exists, e.g. in IR1-CONVERT of one of the legs of
291 ;; 2. It can fail when converting a form which is born orphaned
292 ;; so that it never had a meaningful home lambda, e.g. a form
293 ;; which follows a RETURN-FROM or GO form.
294 (let ((pred-list (block-pred block)))
295 ;; To deal with case 1, we reason that
296 ;; previous-in-target-execution-order blocks should be in the
297 ;; same lambda, and that they seem in practice to be
298 ;; previous-in-compilation-order blocks too, so we look back
299 ;; to find one which is sufficiently initialized to tell us
300 ;; what the home lambda is.
302 ;; We could get fancy about this, flooding through the
303 ;; graph of all the previous blocks, but in practice it
304 ;; seems to work just to grab the first previous block and
306 (node-home-lambda (block-last (first pred-list)))
307 ;; In case 2, we end up with an empty PRED-LIST and
308 ;; have to punt: There's no home lambda.
311 ;;; Return the non-LET LAMBDA that holds BLOCK's code.
312 (defun block-home-lambda (block)
314 (block-home-lambda-or-null block)))
316 ;;; Return the IR1 physical environment for BLOCK.
317 (defun block-physenv (block)
318 (declare (type cblock block))
319 (lambda-physenv (block-home-lambda block)))
321 ;;; Return the Top Level Form number of PATH, i.e. the ordinal number
322 ;;; of its original source's top level form in its compilation unit.
323 (defun source-path-tlf-number (path)
324 (declare (list path))
327 ;;; Return the (reversed) list for the PATH in the original source
328 ;;; (with the Top Level Form number last).
329 (defun source-path-original-source (path)
330 (declare (list path) (inline member))
331 (cddr (member 'original-source-start path :test #'eq)))
333 ;;; Return the Form Number of PATH's original source inside the Top
334 ;;; Level Form that contains it. This is determined by the order that
335 ;;; we walk the subforms of the top level source form.
336 (defun source-path-form-number (path)
337 (declare (list path) (inline member))
338 (cadr (member 'original-source-start path :test #'eq)))
340 ;;; Return a list of all the enclosing forms not in the original
341 ;;; source that converted to get to this form, with the immediate
342 ;;; source for node at the start of the list.
343 (defun source-path-forms (path)
344 (subseq path 0 (position 'original-source-start path)))
346 ;;; Return the innermost source form for NODE.
347 (defun node-source-form (node)
348 (declare (type node node))
349 (let* ((path (node-source-path node))
350 (forms (source-path-forms path)))
353 (values (find-original-source path)))))
355 ;;; Return NODE-SOURCE-FORM, T if continuation has a single use,
356 ;;; otherwise NIL, NIL.
357 (defun continuation-source (cont)
358 (let ((use (continuation-use cont)))
360 (values (node-source-form use) t)
363 ;;; Return the LAMBDA that is CONT's home, or NIL if there is none.
364 (defun continuation-home-lambda-or-null (cont)
365 ;; KLUDGE: This function is a post-CMU-CL hack by WHN, and this
366 ;; implementation might not be quite right, or might be uglier than
367 ;; necessary. It appears that the original Python never found a need
368 ;; to do this operation. The obvious things based on
369 ;; NODE-HOME-LAMBDA of CONTINUATION-USE usually work; then if that
370 ;; fails, BLOCK-HOME-LAMBDA of CONTINUATION-BLOCK works, given that
371 ;; we generalize it enough to grovel harder when the simple CMU CL
372 ;; approach fails, and furthermore realize that in some exceptional
373 ;; cases it might return NIL. -- WHN 2001-12-04
374 (cond ((continuation-use cont)
375 (node-home-lambda (continuation-use cont)))
376 ((continuation-block cont)
377 (block-home-lambda-or-null (continuation-block cont)))
379 (bug "confused about home lambda for ~S"))))
381 ;;; Return the LAMBDA that is CONT's home.
382 (defun continuation-home-lambda (cont)
384 (continuation-home-lambda-or-null cont)))
386 #!-sb-fluid (declaim (inline continuation-single-value-p))
387 (defun continuation-single-value-p (cont)
388 (not (typep (continuation-dest cont)
389 '(or creturn exit mv-combination))))
391 ;;; Return a new LEXENV just like DEFAULT except for the specified
392 ;;; slot values. Values for the alist slots are NCONCed to the
393 ;;; beginning of the current value, rather than replacing it entirely.
394 (defun make-lexenv (&key (default *lexenv*)
395 funs vars blocks tags
396 type-restrictions weakend-type-restrictions
397 (lambda (lexenv-lambda default))
398 (cleanup (lexenv-cleanup default))
399 (policy (lexenv-policy default)))
400 (macrolet ((frob (var slot)
401 `(let ((old (,slot default)))
405 (internal-make-lexenv
406 (frob funs lexenv-funs)
407 (frob vars lexenv-vars)
408 (frob blocks lexenv-blocks)
409 (frob tags lexenv-tags)
410 (frob type-restrictions lexenv-type-restrictions)
411 (frob weakend-type-restrictions lexenv-weakend-type-restrictions)
412 lambda cleanup policy)))
414 ;;; Makes a LEXENV, suitable for using in a MACROLET introduced
416 (defun make-restricted-lexenv (lexenv)
417 (flet ((fun-good-p (fun)
418 (destructuring-bind (name . thing) fun
419 (declare (ignore name))
423 (cons (aver (eq (car thing) 'macro))
426 (destructuring-bind (name . thing) var
427 (declare (ignore name))
430 (cons (aver (eq (car thing) 'macro))
432 (heap-alien-info nil)))))
433 (internal-make-lexenv
434 (remove-if-not #'fun-good-p (lexenv-funs lexenv))
435 (remove-if-not #'var-good-p (lexenv-vars lexenv))
438 (lexenv-type-restrictions lexenv) ; XXX
439 (lexenv-weakend-type-restrictions lexenv)
442 (lexenv-policy lexenv))))
444 ;;;; flow/DFO/component hackery
446 ;;; Join BLOCK1 and BLOCK2.
447 (defun link-blocks (block1 block2)
448 (declare (type cblock block1 block2))
449 (setf (block-succ block1)
450 (if (block-succ block1)
451 (%link-blocks block1 block2)
453 (push block1 (block-pred block2))
455 (defun %link-blocks (block1 block2)
456 (declare (type cblock block1 block2) (inline member))
457 (let ((succ1 (block-succ block1)))
458 (aver (not (member block2 succ1 :test #'eq)))
459 (cons block2 succ1)))
461 ;;; This is like LINK-BLOCKS, but we separate BLOCK1 and BLOCK2. If
462 ;;; this leaves a successor with a single predecessor that ends in an
463 ;;; IF, then set BLOCK-TEST-MODIFIED so that any test constraint will
464 ;;; now be able to be propagated to the successor.
465 (defun unlink-blocks (block1 block2)
466 (declare (type cblock block1 block2))
467 (let ((succ1 (block-succ block1)))
468 (if (eq block2 (car succ1))
469 (setf (block-succ block1) (cdr succ1))
470 (do ((succ (cdr succ1) (cdr succ))
472 ((eq (car succ) block2)
473 (setf (cdr prev) (cdr succ)))
476 (let ((new-pred (delq block1 (block-pred block2))))
477 (setf (block-pred block2) new-pred)
478 (when (and new-pred (null (rest new-pred)))
479 (let ((pred-block (first new-pred)))
480 (when (if-p (block-last pred-block))
481 (setf (block-test-modified pred-block) t)))))
484 ;;; Swing the succ/pred link between BLOCK and OLD to be between BLOCK
485 ;;; and NEW. If BLOCK ends in an IF, then we have to fix up the
486 ;;; consequent/alternative blocks to point to NEW. We also set
487 ;;; BLOCK-TEST-MODIFIED so that any test constraint will be applied to
488 ;;; the new successor.
489 (defun change-block-successor (block old new)
490 (declare (type cblock new old block) (inline member))
491 (unlink-blocks block old)
492 (let ((last (block-last block))
493 (comp (block-component block)))
494 (setf (component-reanalyze comp) t)
497 (setf (block-test-modified block) t)
498 (let* ((succ-left (block-succ block))
499 (new (if (and (eq new (component-tail comp))
503 (unless (member new succ-left :test #'eq)
504 (link-blocks block new))
505 (macrolet ((frob (slot)
506 `(when (eq (,slot last) old)
507 (setf (,slot last) new))))
509 (frob if-alternative)
510 (when (eq (if-consequent last)
511 (if-alternative last))
512 (setf (component-reoptimize (block-component block)) t)))))
514 (unless (member new (block-succ block) :test #'eq)
515 (link-blocks block new)))))
519 ;;; Unlink a block from the next/prev chain. We also null out the
521 (declaim (ftype (function (cblock) (values)) remove-from-dfo))
522 (defun remove-from-dfo (block)
523 (let ((next (block-next block))
524 (prev (block-prev block)))
525 (setf (block-component block) nil)
526 (setf (block-next prev) next)
527 (setf (block-prev next) prev))
530 ;;; Add BLOCK to the next/prev chain following AFTER. We also set the
531 ;;; COMPONENT to be the same as for AFTER.
532 (defun add-to-dfo (block after)
533 (declare (type cblock block after))
534 (let ((next (block-next after))
535 (comp (block-component after)))
536 (aver (not (eq (component-kind comp) :deleted)))
537 (setf (block-component block) comp)
538 (setf (block-next after) block)
539 (setf (block-prev block) after)
540 (setf (block-next block) next)
541 (setf (block-prev next) block))
544 ;;; Set the FLAG for all the blocks in COMPONENT to NIL, except for
545 ;;; the head and tail which are set to T.
546 (declaim (ftype (function (component) (values)) clear-flags))
547 (defun clear-flags (component)
548 (let ((head (component-head component))
549 (tail (component-tail component)))
550 (setf (block-flag head) t)
551 (setf (block-flag tail) t)
552 (do-blocks (block component)
553 (setf (block-flag block) nil)))
556 ;;; Make a component with no blocks in it. The BLOCK-FLAG is initially
557 ;;; true in the head and tail blocks.
558 (declaim (ftype (function nil component) make-empty-component))
559 (defun make-empty-component ()
560 (let* ((head (make-block-key :start nil :component nil))
561 (tail (make-block-key :start nil :component nil))
562 (res (make-component :head head :tail tail)))
563 (setf (block-flag head) t)
564 (setf (block-flag tail) t)
565 (setf (block-component head) res)
566 (setf (block-component tail) res)
567 (setf (block-next head) tail)
568 (setf (block-prev tail) head)
571 ;;; Make NODE the LAST node in its block, splitting the block if necessary.
572 ;;; The new block is added to the DFO immediately following NODE's block.
573 (defun node-ends-block (node)
574 (declare (type node node))
575 (let* ((block (node-block node))
576 (start (node-cont node))
577 (last (block-last block))
578 (last-cont (node-cont last)))
579 (unless (eq last node)
580 (aver (and (eq (continuation-kind start) :inside-block)
581 (not (block-delete-p block))))
582 (let* ((succ (block-succ block))
584 (make-block-key :start start
585 :component (block-component block)
586 :start-uses (list (continuation-use start))
587 :succ succ :last last)))
588 (setf (continuation-kind start) :block-start)
591 (cons new-block (remove block (block-pred b)))))
592 (setf (block-succ block) ())
593 (setf (block-last block) node)
594 (link-blocks block new-block)
595 (add-to-dfo new-block block)
596 (setf (component-reanalyze (block-component block)) t)
598 (do ((cont start (node-cont (continuation-next cont))))
600 (when (eq (continuation-kind last-cont) :inside-block)
601 (setf (continuation-block last-cont) new-block)))
602 (setf (continuation-block cont) new-block))
604 (setf (block-type-asserted block) t)
605 (setf (block-test-modified block) t))))
611 ;;; Deal with deleting the last (read) reference to a LAMBDA-VAR.
612 (defun delete-lambda-var (leaf)
613 (declare (type lambda-var leaf))
615 ;; Iterate over all local calls flushing the corresponding argument,
616 ;; allowing the computation of the argument to be deleted. We also
617 ;; mark the LET for reoptimization, since it may be that we have
618 ;; deleted its last variable.
619 (let* ((fun (lambda-var-home leaf))
620 (n (position leaf (lambda-vars fun))))
621 (dolist (ref (leaf-refs fun))
622 (let* ((cont (node-cont ref))
623 (dest (continuation-dest cont)))
624 (when (and (combination-p dest)
625 (eq (basic-combination-fun dest) cont)
626 (eq (basic-combination-kind dest) :local))
627 (let* ((args (basic-combination-args dest))
629 (reoptimize-continuation arg)
631 (setf (elt args n) nil))))))
633 ;; The LAMBDA-VAR may still have some SETs, but this doesn't cause
634 ;; too much difficulty, since we can efficiently implement
635 ;; write-only variables. We iterate over the SETs, marking their
636 ;; blocks for dead code flushing, since we can delete SETs whose
638 (dolist (set (lambda-var-sets leaf))
639 (setf (block-flush-p (node-block set)) t))
643 ;;; Note that something interesting has happened to VAR.
644 (defun reoptimize-lambda-var (var)
645 (declare (type lambda-var var))
646 (let ((fun (lambda-var-home var)))
647 ;; We only deal with LET variables, marking the corresponding
648 ;; initial value arg as needing to be reoptimized.
649 (when (and (eq (functional-kind fun) :let)
651 (do ((args (basic-combination-args
654 (first (leaf-refs fun)))))
656 (vars (lambda-vars fun) (cdr vars)))
658 (reoptimize-continuation (car args))))))
661 ;;; Delete a function that has no references. This need only be called
662 ;;; on functions that never had any references, since otherwise
663 ;;; DELETE-REF will handle the deletion.
664 (defun delete-functional (fun)
665 (aver (and (null (leaf-refs fun))
666 (not (functional-entry-fun fun))))
668 (optional-dispatch (delete-optional-dispatch fun))
669 (clambda (delete-lambda fun)))
672 ;;; Deal with deleting the last reference to a CLAMBDA. Since there is
673 ;;; only one way into a CLAMBDA, deleting the last reference to a
674 ;;; CLAMBDA ensures that there is no way to reach any of the code in
675 ;;; it. So we just set the FUNCTIONAL-KIND for FUN and its LETs to
676 ;;; :DELETED, causing IR1 optimization to delete blocks in that
678 (defun delete-lambda (clambda)
679 (declare (type clambda clambda))
680 (let ((original-kind (functional-kind clambda))
681 (bind (lambda-bind clambda)))
682 (aver (not (member original-kind '(:deleted :optional :toplevel))))
683 (aver (not (functional-has-external-references-p clambda)))
684 (setf (functional-kind clambda) :deleted)
685 (setf (lambda-bind clambda) nil)
686 (dolist (let (lambda-lets clambda))
687 (setf (lambda-bind let) nil)
688 (setf (functional-kind let) :deleted))
690 ;; LET may be deleted if its BIND is unreachable. Autonomous
691 ;; function may be deleted if it has no reachable references.
692 (unless (member original-kind '(:let :mv-let :assignment))
693 (dolist (ref (lambda-refs clambda))
694 (mark-for-deletion (node-block ref))))
696 ;; (The IF test is (FUNCTIONAL-SOMEWHAT-LETLIKE-P CLAMBDA), except
697 ;; that we're using the old value of the KIND slot, not the
698 ;; current slot value, which has now been set to :DELETED.)
699 (if (member original-kind '(:let :mv-let :assignment))
700 (let ((home (lambda-home clambda)))
701 (setf (lambda-lets home) (delete clambda (lambda-lets home))))
702 ;; If the function isn't a LET, we unlink the function head
703 ;; and tail from the component head and tail to indicate that
704 ;; the code is unreachable. We also delete the function from
705 ;; COMPONENT-LAMBDAS (it won't be there before local call
706 ;; analysis, but no matter.) If the lambda was never
707 ;; referenced, we give a note.
708 (let* ((bind-block (node-block bind))
709 (component (block-component bind-block))
710 (return (lambda-return clambda))
711 (return-block (and return (node-block return))))
712 (unless (leaf-ever-used clambda)
713 (let ((*compiler-error-context* bind))
714 (compiler-note "deleting unused function~:[.~;~:*~% ~S~]"
715 (leaf-debug-name clambda))))
716 (unless (block-delete-p bind-block)
717 (unlink-blocks (component-head component) bind-block))
718 (when (and return-block (not (block-delete-p return-block)))
719 (mark-for-deletion return-block)
720 (unlink-blocks return-block (component-tail component)))
721 (setf (component-reanalyze component) t)
722 (let ((tails (lambda-tail-set clambda)))
723 (setf (tail-set-funs tails)
724 (delete clambda (tail-set-funs tails)))
725 (setf (lambda-tail-set clambda) nil))
726 (setf (component-lambdas component)
727 (delete clambda (component-lambdas component)))))
729 ;; If the lambda is an XEP, then we null out the ENTRY-FUN in its
730 ;; ENTRY-FUN so that people will know that it is not an entry
732 (when (eq original-kind :external)
733 (let ((fun (functional-entry-fun clambda)))
734 (setf (functional-entry-fun fun) nil)
735 (when (optional-dispatch-p fun)
736 (delete-optional-dispatch fun)))))
740 ;;; Deal with deleting the last reference to an OPTIONAL-DISPATCH. We
741 ;;; have to be a bit more careful than with lambdas, since DELETE-REF
742 ;;; is used both before and after local call analysis. Afterward, all
743 ;;; references to still-existing OPTIONAL-DISPATCHes have been moved
744 ;;; to the XEP, leaving it with no references at all. So we look at
745 ;;; the XEP to see whether an optional-dispatch is still really being
746 ;;; used. But before local call analysis, there are no XEPs, and all
747 ;;; references are direct.
749 ;;; When we do delete the OPTIONAL-DISPATCH, we grovel all of its
750 ;;; entry-points, making them be normal lambdas, and then deleting the
751 ;;; ones with no references. This deletes any e-p lambdas that were
752 ;;; either never referenced, or couldn't be deleted when the last
753 ;;; reference was deleted (due to their :OPTIONAL kind.)
755 ;;; Note that the last optional entry point may alias the main entry,
756 ;;; so when we process the main entry, its KIND may have been changed
757 ;;; to NIL or even converted to a LETlike value.
758 (defun delete-optional-dispatch (leaf)
759 (declare (type optional-dispatch leaf))
760 (let ((entry (functional-entry-fun leaf)))
761 (unless (and entry (leaf-refs entry))
762 (aver (or (not entry) (eq (functional-kind entry) :deleted)))
763 (setf (functional-kind leaf) :deleted)
766 (unless (eq (functional-kind fun) :deleted)
767 (aver (eq (functional-kind fun) :optional))
768 (setf (functional-kind fun) nil)
769 (let ((refs (leaf-refs fun)))
773 (or (maybe-let-convert fun)
774 (maybe-convert-to-assignment fun)))
776 (maybe-convert-to-assignment fun)))))))
778 (dolist (ep (optional-dispatch-entry-points leaf))
780 (when (optional-dispatch-more-entry leaf)
781 (frob (optional-dispatch-more-entry leaf)))
782 (let ((main (optional-dispatch-main-entry leaf)))
783 (when (eq (functional-kind main) :optional)
788 ;;; Do stuff to delete the semantic attachments of a REF node. When
789 ;;; this leaves zero or one reference, we do a type dispatch off of
790 ;;; the leaf to determine if a special action is appropriate.
791 (defun delete-ref (ref)
792 (declare (type ref ref))
793 (let* ((leaf (ref-leaf ref))
794 (refs (delete ref (leaf-refs leaf))))
795 (setf (leaf-refs leaf) refs)
800 (delete-lambda-var leaf))
802 (ecase (functional-kind leaf)
803 ((nil :let :mv-let :assignment :escape :cleanup)
804 (aver (null (functional-entry-fun leaf)))
805 (delete-lambda leaf))
807 (delete-lambda leaf))
808 ((:deleted :optional))))
810 (unless (eq (functional-kind leaf) :deleted)
811 (delete-optional-dispatch leaf)))))
814 (clambda (or (maybe-let-convert leaf)
815 (maybe-convert-to-assignment leaf)))
816 (lambda-var (reoptimize-lambda-var leaf))))
819 (clambda (maybe-convert-to-assignment leaf))))))
823 ;;; This function is called by people who delete nodes; it provides a
824 ;;; way to indicate that the value of a continuation is no longer
825 ;;; used. We null out the CONTINUATION-DEST, set FLUSH-P in the blocks
826 ;;; containing uses of CONT and set COMPONENT-REOPTIMIZE. If the PREV
827 ;;; of the use is deleted, then we blow off reoptimization.
829 ;;; If the continuation is :DELETED, then we don't do anything, since
830 ;;; all semantics have already been flushed. :DELETED-BLOCK-START
831 ;;; start continuations are treated just like :BLOCK-START; it is
832 ;;; possible that the continuation may be given a new dest (e.g. by
833 ;;; SUBSTITUTE-CONTINUATION), so we don't want to delete it.
834 (defun flush-dest (cont)
835 (declare (type continuation cont))
837 (unless (eq (continuation-kind cont) :deleted)
838 (aver (continuation-dest cont))
839 (setf (continuation-dest cont) nil)
840 (setf (continuation-%externally-checkable-type cont) nil)
842 (let ((prev (node-prev use)))
843 (unless (eq (continuation-kind prev) :deleted)
844 (let ((block (continuation-block prev)))
845 (setf (component-reoptimize (block-component block)) t)
846 (setf (block-attributep (block-flags block) flush-p type-asserted)
849 (setf (continuation-%type-check cont) nil)
853 ;;; Do a graph walk backward from BLOCK, marking all predecessor
854 ;;; blocks with the DELETE-P flag.
855 (defun mark-for-deletion (block)
856 (declare (type cblock block))
857 (let* ((component (block-component block))
858 (head (component-head component)))
859 (labels ((helper (block)
860 (setf (block-delete-p block) t)
861 (dolist (pred (block-pred block))
862 (unless (or (block-delete-p pred)
865 (unless (block-delete-p block)
867 (setf (component-reanalyze component) t))))
870 ;;; Delete CONT, eliminating both control and value semantics. We set
871 ;;; FLUSH-P and COMPONENT-REOPTIMIZE similarly to in FLUSH-DEST. Here
872 ;;; we must get the component from the use block, since the
873 ;;; continuation may be a :DELETED-BLOCK-START.
875 ;;; If CONT has DEST, then it must be the case that the DEST is
876 ;;; unreachable, since we can't compute the value desired. In this
877 ;;; case, we call MARK-FOR-DELETION to cause the DEST block and its
878 ;;; predecessors to tell people to ignore them, and to cause them to
879 ;;; be deleted eventually.
880 (defun delete-continuation (cont)
881 (declare (type continuation cont))
882 (aver (not (eq (continuation-kind cont) :deleted)))
885 (let ((prev (node-prev use)))
886 (unless (eq (continuation-kind prev) :deleted)
887 (let ((block (continuation-block prev)))
888 (setf (block-attributep (block-flags block) flush-p type-asserted) t)
889 (setf (component-reoptimize (block-component block)) t)))))
891 (let ((dest (continuation-dest cont)))
893 (let ((prev (node-prev dest)))
895 (not (eq (continuation-kind prev) :deleted)))
896 (let ((block (continuation-block prev)))
897 (unless (block-delete-p block)
898 (mark-for-deletion block)))))))
900 (setf (continuation-kind cont) :deleted)
901 (setf (continuation-dest cont) nil)
902 (setf (continuation-%externally-checkable-type cont) nil)
903 (setf (continuation-next cont) nil)
904 (setf (continuation-asserted-type cont) *empty-type*)
905 (setf (continuation-%derived-type cont) *empty-type*)
906 (setf (continuation-type-to-check cont) *empty-type*)
907 (setf (continuation-use cont) nil)
908 (setf (continuation-block cont) nil)
909 (setf (continuation-reoptimize cont) nil)
910 (setf (continuation-%type-check cont) nil)
911 (setf (continuation-info cont) nil)
915 ;;; This function does what is necessary to eliminate the code in it
916 ;;; from the IR1 representation. This involves unlinking it from its
917 ;;; predecessors and successors and deleting various node-specific
918 ;;; semantic information.
920 ;;; We mark the START as has having no next and remove the last node
921 ;;; from its CONT's uses. We also flush the DEST for all continuations
922 ;;; whose values are received by nodes in the block.
923 (defun delete-block (block)
924 (declare (type cblock block))
925 (aver (block-component block)) ; else block is already deleted!
926 (note-block-deletion block)
927 (setf (block-delete-p block) t)
929 (let* ((last (block-last block))
930 (cont (node-cont last)))
931 (delete-continuation-use last)
932 (if (eq (continuation-kind cont) :unused)
933 (delete-continuation cont)
934 (reoptimize-continuation cont)))
936 (dolist (b (block-pred block))
937 (unlink-blocks b block)
938 ;; In bug 147 the almost-all-blocks-have-a-successor invariant was
939 ;; broken when successors were deleted without setting the
940 ;; BLOCK-DELETE-P flags of their predececessors. Make sure that
941 ;; doesn't happen again.
942 (aver (not (and (null (block-succ b))
943 (not (block-delete-p b))
944 (not (eq b (component-head (block-component b))))))))
945 (dolist (b (block-succ block))
946 (unlink-blocks block b))
948 (do-nodes (node cont block)
950 (ref (delete-ref node))
952 (flush-dest (if-test node)))
953 ;; The next two cases serve to maintain the invariant that a LET
954 ;; always has a well-formed COMBINATION, REF and BIND. We delete
955 ;; the lambda whenever we delete any of these, but we must be
956 ;; careful that this LET has not already been partially deleted.
958 (when (and (eq (basic-combination-kind node) :local)
959 ;; Guards COMBINATION-LAMBDA agains the REF being deleted.
960 (continuation-use (basic-combination-fun node)))
961 (let ((fun (combination-lambda node)))
962 ;; If our REF was the second-to-last ref, and has been
963 ;; deleted, then FUN may be a LET for some other
965 (when (and (functional-letlike-p fun)
966 (eq (let-combination fun) node))
967 (delete-lambda fun))))
968 (flush-dest (basic-combination-fun node))
969 (dolist (arg (basic-combination-args node))
970 (when arg (flush-dest arg))))
972 (let ((lambda (bind-lambda node)))
973 (unless (eq (functional-kind lambda) :deleted)
974 (delete-lambda lambda))))
976 (let ((value (exit-value node))
977 (entry (exit-entry node)))
981 (setf (entry-exits entry)
982 (delete node (entry-exits entry))))))
984 (flush-dest (return-result node))
985 (delete-return node))
987 (flush-dest (set-value node))
988 (let ((var (set-var node)))
989 (setf (basic-var-sets var)
990 (delete node (basic-var-sets var))))))
992 (delete-continuation (node-prev node)))
994 (remove-from-dfo block)
997 ;;; Do stuff to indicate that the return node Node is being deleted.
998 ;;; We set the RETURN to NIL.
999 (defun delete-return (node)
1000 (declare (type creturn node))
1001 (let ((fun (return-lambda node)))
1002 (aver (lambda-return fun))
1003 (setf (lambda-return fun) nil))
1006 ;;; If any of the VARS in FUN was never referenced and was not
1007 ;;; declared IGNORE, then complain.
1008 (defun note-unreferenced-vars (fun)
1009 (declare (type clambda fun))
1010 (dolist (var (lambda-vars fun))
1011 (unless (or (leaf-ever-used var)
1012 (lambda-var-ignorep var))
1013 (let ((*compiler-error-context* (lambda-bind fun)))
1014 (unless (policy *compiler-error-context* (= inhibit-warnings 3))
1015 ;; ANSI section "3.2.5 Exceptional Situations in the Compiler"
1016 ;; requires this to be no more than a STYLE-WARNING.
1017 (compiler-style-warn "The variable ~S is defined but never used."
1018 (leaf-debug-name var)))
1019 (setf (leaf-ever-used var) t)))) ; to avoid repeated warnings? -- WHN
1022 (defvar *deletion-ignored-objects* '(t nil))
1024 ;;; Return true if we can find OBJ in FORM, NIL otherwise. We bound
1025 ;;; our recursion so that we don't get lost in circular structures. We
1026 ;;; ignore the car of forms if they are a symbol (to prevent confusing
1027 ;;; function referencess with variables), and we also ignore anything
1029 (defun present-in-form (obj form depth)
1030 (declare (type (integer 0 20) depth))
1031 (cond ((= depth 20) nil)
1035 (let ((first (car form))
1037 (if (member first '(quote function))
1039 (or (and (not (symbolp first))
1040 (present-in-form obj first depth))
1041 (do ((l (cdr form) (cdr l))
1043 ((or (atom l) (> n 100))
1045 (declare (fixnum n))
1046 (when (present-in-form obj (car l) depth)
1049 ;;; This function is called on a block immediately before we delete
1050 ;;; it. We check to see whether any of the code about to die appeared
1051 ;;; in the original source, and emit a note if so.
1053 ;;; If the block was in a lambda is now deleted, then we ignore the
1054 ;;; whole block, since this case is picked off in DELETE-LAMBDA. We
1055 ;;; also ignore the deletion of CRETURN nodes, since it is somewhat
1056 ;;; reasonable for a function to not return, and there is a different
1057 ;;; note for that case anyway.
1059 ;;; If the actual source is an atom, then we use a bunch of heuristics
1060 ;;; to guess whether this reference really appeared in the original
1062 ;;; -- If a symbol, it must be interned and not a keyword.
1063 ;;; -- It must not be an easily introduced constant (T or NIL, a fixnum
1064 ;;; or a character.)
1065 ;;; -- The atom must be "present" in the original source form, and
1066 ;;; present in all intervening actual source forms.
1067 (defun note-block-deletion (block)
1068 (let ((home (block-home-lambda block)))
1069 (unless (eq (functional-kind home) :deleted)
1070 (do-nodes (node cont block)
1071 (let* ((path (node-source-path node))
1072 (first (first path)))
1073 (when (or (eq first 'original-source-start)
1075 (or (not (symbolp first))
1076 (let ((pkg (symbol-package first)))
1078 (not (eq pkg (symbol-package :end))))))
1079 (not (member first *deletion-ignored-objects*))
1080 (not (typep first '(or fixnum character)))
1082 (present-in-form first x 0))
1083 (source-path-forms path))
1084 (present-in-form first (find-original-source path)
1086 (unless (return-p node)
1087 (let ((*compiler-error-context* node))
1088 (compiler-note "deleting unreachable code")))
1092 ;;; Delete a node from a block, deleting the block if there are no
1093 ;;; nodes left. We remove the node from the uses of its CONT, but we
1094 ;;; don't deal with cleaning up any type-specific semantic
1095 ;;; attachments. If the CONT is :UNUSED after deleting this use, then
1096 ;;; we delete CONT. (Note :UNUSED is not the same as no uses. A
1097 ;;; continuation will only become :UNUSED if it was :INSIDE-BLOCK
1100 ;;; If the node is the last node, there must be exactly one successor.
1101 ;;; We link all of our precedessors to the successor and unlink the
1102 ;;; block. In this case, we return T, otherwise NIL. If no nodes are
1103 ;;; left, and the block is a successor of itself, then we replace the
1104 ;;; only node with a degenerate exit node. This provides a way to
1105 ;;; represent the bodyless infinite loop, given the prohibition on
1106 ;;; empty blocks in IR1.
1107 (defun unlink-node (node)
1108 (declare (type node node))
1109 (let* ((cont (node-cont node))
1110 (next (continuation-next cont))
1111 (prev (node-prev node))
1112 (block (continuation-block prev))
1113 (prev-kind (continuation-kind prev))
1114 (last (block-last block)))
1116 (unless (eq (continuation-kind cont) :deleted)
1117 (delete-continuation-use node)
1118 (when (eq (continuation-kind cont) :unused)
1119 (aver (not (continuation-dest cont)))
1120 (delete-continuation cont)))
1122 (setf (block-type-asserted block) t)
1123 (setf (block-test-modified block) t)
1125 (cond ((or (eq prev-kind :inside-block)
1126 (and (eq prev-kind :block-start)
1127 (not (eq node last))))
1128 (cond ((eq node last)
1129 (setf (block-last block) (continuation-use prev))
1130 (setf (continuation-next prev) nil))
1132 (setf (continuation-next prev) next)
1133 (setf (node-prev next) prev)))
1134 (setf (node-prev node) nil)
1137 (aver (eq prev-kind :block-start))
1138 (aver (eq node last))
1139 (let* ((succ (block-succ block))
1140 (next (first succ)))
1141 (aver (and succ (null (cdr succ))))
1143 ((member block succ)
1144 (with-ir1-environment-from-node node
1145 (let ((exit (make-exit))
1146 (dummy (make-continuation)))
1147 (setf (continuation-next prev) nil)
1148 (link-node-to-previous-continuation exit prev)
1149 (add-continuation-use exit dummy)
1150 (setf (block-last block) exit)))
1151 (setf (node-prev node) nil)
1154 (aver (eq (block-start-cleanup block)
1155 (block-end-cleanup block)))
1156 (unlink-blocks block next)
1157 (dolist (pred (block-pred block))
1158 (change-block-successor pred block next))
1159 (remove-from-dfo block)
1160 (cond ((continuation-dest prev)
1161 (setf (continuation-next prev) nil)
1162 (setf (continuation-kind prev) :deleted-block-start))
1164 (delete-continuation prev)))
1165 (setf (node-prev node) nil)
1168 ;;; Return true if NODE has been deleted, false if it is still a valid
1170 (defun node-deleted (node)
1171 (declare (type node node))
1172 (let ((prev (node-prev node)))
1174 (not (eq (continuation-kind prev) :deleted))
1175 (let ((block (continuation-block prev)))
1176 (and (block-component block)
1177 (not (block-delete-p block))))))))
1179 ;;; Delete all the blocks and functions in COMPONENT. We scan first
1180 ;;; marking the blocks as DELETE-P to prevent weird stuff from being
1181 ;;; triggered by deletion.
1182 (defun delete-component (component)
1183 (declare (type component component))
1184 (aver (null (component-new-functionals component)))
1185 (setf (component-kind component) :deleted)
1186 (do-blocks (block component)
1187 (setf (block-delete-p block) t))
1188 (dolist (fun (component-lambdas component))
1189 (setf (functional-kind fun) nil)
1190 (setf (functional-entry-fun fun) nil)
1191 (setf (leaf-refs fun) nil)
1192 (delete-functional fun))
1193 (do-blocks (block component)
1194 (delete-block block))
1197 ;;; Convert code of the form
1198 ;;; (FOO ... (FUN ...) ...)
1200 ;;; (FOO ... ... ...).
1201 ;;; In other words, replace the function combination FUN by its
1202 ;;; arguments. If there are any problems with doing this, use GIVE-UP
1203 ;;; to blow out of whatever transform called this. Note, as the number
1204 ;;; of arguments changes, the transform must be prepared to return a
1205 ;;; lambda with a new lambda-list with the correct number of
1207 (defun extract-fun-args (cont fun num-args)
1209 "If CONT is a call to FUN with NUM-ARGS args, change those arguments
1210 to feed directly to the continuation-dest of CONT, which must be
1212 (declare (type continuation cont)
1214 (type index num-args))
1215 (let ((outside (continuation-dest cont))
1216 (inside (continuation-use cont)))
1217 (aver (combination-p outside))
1218 (unless (combination-p inside)
1219 (give-up-ir1-transform))
1220 (let ((inside-fun (combination-fun inside)))
1221 (unless (eq (continuation-fun-name inside-fun) fun)
1222 (give-up-ir1-transform))
1223 (let ((inside-args (combination-args inside)))
1224 (unless (= (length inside-args) num-args)
1225 (give-up-ir1-transform))
1226 (let* ((outside-args (combination-args outside))
1227 (arg-position (position cont outside-args))
1228 (before-args (subseq outside-args 0 arg-position))
1229 (after-args (subseq outside-args (1+ arg-position))))
1230 (dolist (arg inside-args)
1231 (setf (continuation-dest arg) outside)
1232 (setf (continuation-%externally-checkable-type arg) nil))
1233 (setf (combination-args inside) nil)
1234 (setf (combination-args outside)
1235 (append before-args inside-args after-args))
1236 (change-ref-leaf (continuation-use inside-fun)
1237 (find-free-fun 'list "???"))
1238 (setf (combination-kind inside) :full)
1239 (setf (node-derived-type inside) *wild-type*)
1241 (setf (continuation-asserted-type cont) *wild-type*)
1242 (setf (continuation-type-to-check cont) *wild-type*)
1247 ;;; Change the LEAF that a REF refers to.
1248 (defun change-ref-leaf (ref leaf)
1249 (declare (type ref ref) (type leaf leaf))
1250 (unless (eq (ref-leaf ref) leaf)
1251 (push ref (leaf-refs leaf))
1253 (setf (ref-leaf ref) leaf)
1254 (setf (leaf-ever-used leaf) t)
1255 (let ((ltype (leaf-type leaf)))
1256 (if (fun-type-p ltype)
1257 (setf (node-derived-type ref) ltype)
1258 (derive-node-type ref ltype)))
1259 (reoptimize-continuation (node-cont ref)))
1262 ;;; Change all REFS for OLD-LEAF to NEW-LEAF.
1263 (defun substitute-leaf (new-leaf old-leaf)
1264 (declare (type leaf new-leaf old-leaf))
1265 (dolist (ref (leaf-refs old-leaf))
1266 (change-ref-leaf ref new-leaf))
1269 ;;; like SUBSITUTE-LEAF, only there is a predicate on the REF to tell
1270 ;;; whether to substitute
1271 (defun substitute-leaf-if (test new-leaf old-leaf)
1272 (declare (type leaf new-leaf old-leaf) (type function test))
1273 (dolist (ref (leaf-refs old-leaf))
1274 (when (funcall test ref)
1275 (change-ref-leaf ref new-leaf)))
1278 ;;; Return a LEAF which represents the specified constant object. If
1279 ;;; the object is not in *CONSTANTS*, then we create a new constant
1280 ;;; LEAF and enter it.
1281 (defun find-constant (object)
1283 ;; FIXME: What is the significance of this test? ("things
1284 ;; that are worth uniquifying"?)
1285 '(or symbol number character instance))
1286 (or (gethash object *constants*)
1287 (setf (gethash object *constants*)
1288 (make-constant :value object
1289 :%source-name '.anonymous.
1290 :type (ctype-of object)
1291 :where-from :defined)))
1292 (make-constant :value object
1293 :%source-name '.anonymous.
1294 :type (ctype-of object)
1295 :where-from :defined)))
1297 ;;; If there is a non-local exit noted in ENTRY's environment that
1298 ;;; exits to CONT in that entry, then return it, otherwise return NIL.
1299 (defun find-nlx-info (entry cont)
1300 (declare (type entry entry) (type continuation cont))
1301 (let ((entry-cleanup (entry-cleanup entry)))
1302 (dolist (nlx (physenv-nlx-info (node-physenv entry)) nil)
1303 (when (and (eq (nlx-info-continuation nlx) cont)
1304 (eq (nlx-info-cleanup nlx) entry-cleanup))
1307 ;;;; functional hackery
1309 (declaim (ftype (function (functional) clambda) main-entry))
1310 (defun main-entry (functional)
1311 (etypecase functional
1312 (clambda functional)
1314 (optional-dispatch-main-entry functional))))
1316 ;;; RETURN true if FUNCTIONAL is a thing that can be treated like
1317 ;;; MV-BIND when it appears in an MV-CALL. All fixed arguments must be
1318 ;;; optional with null default and no SUPPLIED-P. There must be a
1319 ;;; &REST arg with no references.
1320 (declaim (ftype (function (functional) boolean) looks-like-an-mv-bind))
1321 (defun looks-like-an-mv-bind (functional)
1322 (and (optional-dispatch-p functional)
1323 (do ((arg (optional-dispatch-arglist functional) (cdr arg)))
1325 (let ((info (lambda-var-arg-info (car arg))))
1326 (unless info (return nil))
1327 (case (arg-info-kind info)
1329 (when (or (arg-info-supplied-p info) (arg-info-default info))
1332 (return (and (null (cdr arg)) (null (leaf-refs (car arg))))))
1336 ;;; Return true if function is an external entry point. This is true
1337 ;;; of normal XEPs (:EXTERNAL kind) and also of top level lambdas
1338 ;;; (:TOPLEVEL kind.)
1340 (declare (type functional fun))
1341 (not (null (member (functional-kind fun) '(:external :toplevel)))))
1343 ;;; If CONT's only use is a non-notinline global function reference,
1344 ;;; then return the referenced symbol, otherwise NIL. If NOTINLINE-OK
1345 ;;; is true, then we don't care if the leaf is NOTINLINE.
1346 (defun continuation-fun-name (cont &optional notinline-ok)
1347 (declare (type continuation cont))
1348 (let ((use (continuation-use cont)))
1350 (let ((leaf (ref-leaf use)))
1351 (if (and (global-var-p leaf)
1352 (eq (global-var-kind leaf) :global-function)
1353 (or (not (defined-fun-p leaf))
1354 (not (eq (defined-fun-inlinep leaf) :notinline))
1356 (leaf-source-name leaf)
1360 ;;; Return the source name of a combination. (This is an idiom
1361 ;;; which was used in CMU CL. I gather it always works. -- WHN)
1362 (defun combination-fun-source-name (combination)
1363 (let ((ref (continuation-use (combination-fun combination))))
1364 (leaf-source-name (ref-leaf ref))))
1366 ;;; Return the COMBINATION node that is the call to the LET FUN.
1367 (defun let-combination (fun)
1368 (declare (type clambda fun))
1369 (aver (functional-letlike-p fun))
1370 (continuation-dest (node-cont (first (leaf-refs fun)))))
1372 ;;; Return the initial value continuation for a LET variable, or NIL
1373 ;;; if there is none.
1374 (defun let-var-initial-value (var)
1375 (declare (type lambda-var var))
1376 (let ((fun (lambda-var-home var)))
1377 (elt (combination-args (let-combination fun))
1378 (position-or-lose var (lambda-vars fun)))))
1380 ;;; Return the LAMBDA that is called by the local CALL.
1381 (defun combination-lambda (call)
1382 (declare (type basic-combination call))
1383 (aver (eq (basic-combination-kind call) :local))
1384 (ref-leaf (continuation-use (basic-combination-fun call))))
1386 (defvar *inline-expansion-limit* 200
1388 "an upper limit on the number of inline function calls that will be expanded
1389 in any given code object (single function or block compilation)")
1391 ;;; Check whether NODE's component has exceeded its inline expansion
1392 ;;; limit, and warn if so, returning NIL.
1393 (defun inline-expansion-ok (node)
1394 (let ((expanded (incf (component-inline-expansions
1396 (node-block node))))))
1397 (cond ((> expanded *inline-expansion-limit*) nil)
1398 ((= expanded *inline-expansion-limit*)
1399 ;; FIXME: If the objective is to stop the recursive
1400 ;; expansion of inline functions, wouldn't it be more
1401 ;; correct to look back through surrounding expansions
1402 ;; (which are, I think, stored in the *CURRENT-PATH*, and
1403 ;; possibly stored elsewhere too) and suppress expansion
1404 ;; and print this warning when the function being proposed
1405 ;; for inline expansion is found there? (I don't like the
1406 ;; arbitrary numerical limit in principle, and I think
1407 ;; it'll be a nuisance in practice if we ever want the
1408 ;; compiler to be able to use WITH-COMPILATION-UNIT on
1409 ;; arbitrarily huge blocks of code. -- WHN)
1410 (let ((*compiler-error-context* node))
1411 (compiler-note "*INLINE-EXPANSION-LIMIT* (~W) was exceeded, ~
1412 probably trying to~% ~
1413 inline a recursive function."
1414 *inline-expansion-limit*))
1420 ;;; Apply a function to some arguments, returning a list of the values
1421 ;;; resulting of the evaluation. If an error is signalled during the
1422 ;;; application, then we produce a warning message using WARN-FUN and
1423 ;;; return NIL as our second value to indicate this. NODE is used as
1424 ;;; the error context for any error message, and CONTEXT is a string
1425 ;;; that is spliced into the warning.
1426 (declaim (ftype (function ((or symbol function) list node function string)
1427 (values list boolean))
1429 (defun careful-call (function args node warn-fun context)
1431 (multiple-value-list
1432 (handler-case (apply function args)
1434 (let ((*compiler-error-context* node))
1435 (funcall warn-fun "Lisp error during ~A:~%~A" context condition)
1436 (return-from careful-call (values nil nil))))))
1439 ;;; Variations of SPECIFIER-TYPE for parsing possibly wrong
1442 ((deffrob (basic careful compiler transform)
1444 (defun ,careful (specifier)
1445 (handler-case (,basic specifier)
1446 (simple-error (condition)
1447 (values nil (list* (simple-condition-format-control condition)
1448 (simple-condition-format-arguments condition))))))
1449 (defun ,compiler (specifier)
1450 (multiple-value-bind (type error-args) (,careful specifier)
1452 (apply #'compiler-error error-args))))
1453 (defun ,transform (specifier)
1454 (multiple-value-bind (type error-args) (,careful specifier)
1456 (apply #'give-up-ir1-transform
1458 (deffrob specifier-type careful-specifier-type compiler-specifier-type ir1-transform-specifier-type)
1459 (deffrob values-specifier-type careful-values-specifier-type compiler-values-specifier-type ir1-transform-values-specifier-type))
1462 ;;;; utilities used at run-time for parsing &KEY args in IR1
1464 ;;; This function is used by the result of PARSE-DEFTRANSFORM to find
1465 ;;; the continuation for the value of the &KEY argument KEY in the
1466 ;;; list of continuations ARGS. It returns the continuation if the
1467 ;;; keyword is present, or NIL otherwise. The legality and
1468 ;;; constantness of the keywords should already have been checked.
1469 (declaim (ftype (function (list keyword) (or continuation null))
1470 find-keyword-continuation))
1471 (defun find-keyword-continuation (args key)
1472 (do ((arg args (cddr arg)))
1474 (when (eq (continuation-value (first arg)) key)
1475 (return (second arg)))))
1477 ;;; This function is used by the result of PARSE-DEFTRANSFORM to
1478 ;;; verify that alternating continuations in ARGS are constant and
1479 ;;; that there is an even number of args.
1480 (declaim (ftype (function (list) boolean) check-key-args-constant))
1481 (defun check-key-args-constant (args)
1482 (do ((arg args (cddr arg)))
1484 (unless (and (rest arg)
1485 (constant-continuation-p (first arg)))
1488 ;;; This function is used by the result of PARSE-DEFTRANSFORM to
1489 ;;; verify that the list of continuations ARGS is a well-formed &KEY
1490 ;;; arglist and that only keywords present in the list KEYS are
1492 (declaim (ftype (function (list list) boolean) check-transform-keys))
1493 (defun check-transform-keys (args keys)
1494 (and (check-key-args-constant args)
1495 (do ((arg args (cddr arg)))
1497 (unless (member (continuation-value (first arg)) keys)
1502 ;;; Called by the expansion of the EVENT macro.
1503 (declaim (ftype (function (event-info (or node null)) *) %event))
1504 (defun %event (info node)
1505 (incf (event-info-count info))
1506 (when (and (>= (event-info-level info) *event-note-threshold*)
1507 (policy (or node *lexenv*)
1508 (= inhibit-warnings 0)))
1509 (let ((*compiler-error-context* node))
1510 (compiler-note (event-info-description info))))
1512 (let ((action (event-info-action info)))
1513 (when action (funcall action node))))