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 none in
18 ;;; its function. If Node has no cleanup, but is in a let, then we must still
19 ;;; 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 an
29 ;;; implicit MV-Prog1. The inserted block is returned. Node is used for IR1
30 ;;; context when converting the form. Note that the block is not assigned a
31 ;;; number, and is linked into the DFO at the beginning. We indicate that we
32 ;;; have trashed the DFO by setting Component-Reanalyze. If Cleanup is
33 ;;; supplied, then convert with that cleanup.
34 (defun insert-cleanup-code (block1 block2 node form &optional cleanup)
35 (declare (type cblock block1 block2) (type node node)
36 (type (or cleanup null) cleanup))
37 (setf (component-reanalyze (block-component block1)) t)
38 (with-ir1-environment node
39 (let* ((start (make-continuation))
40 (block (continuation-starts-block start))
41 (cont (make-continuation))
43 (make-lexenv :cleanup cleanup)
45 (change-block-successor block1 block2 block)
46 (link-blocks block block2)
47 (ir1-convert start cont form)
48 (setf (block-last block) (continuation-use cont))
51 ;;;; continuation use hacking
53 ;;; Return a list of all the nodes which use Cont.
54 (declaim (ftype (function (continuation) list) find-uses))
55 (defun find-uses (cont)
56 (ecase (continuation-kind cont)
57 ((:block-start :deleted-block-start)
58 (block-start-uses (continuation-block cont)))
59 (:inside-block (list (continuation-use cont)))
63 ;;; Update continuation use information so that Node is no longer a
64 ;;; use of its Cont. If the old continuation doesn't start its block,
65 ;;; then we don't update the Block-Start-Uses, since it will be
66 ;;; deleted when we are done.
68 ;;; Note: if you call this function, you may have to do a
69 ;;; REOPTIMIZE-CONTINUATION to inform IR1 optimization that something
71 (declaim (ftype (function (node) (values)) delete-continuation-use))
72 (defun delete-continuation-use (node)
73 (let* ((cont (node-cont node))
74 (block (continuation-block cont)))
75 (ecase (continuation-kind cont)
77 ((:block-start :deleted-block-start)
78 (let ((uses (delete node (block-start-uses block))))
79 (setf (block-start-uses block) uses)
80 (setf (continuation-use cont)
81 (if (cdr uses) nil (car uses)))))
83 (setf (continuation-kind cont) :unused)
84 (setf (continuation-block cont) nil)
85 (setf (continuation-use cont) nil)
86 (setf (continuation-next cont) nil)))
87 (setf (node-cont node) nil))
90 ;;; Update continuation use information so that Node uses Cont. If
91 ;;; Cont is :Unused, then we set its block to Node's Node-Block (which
94 ;;; Note: if you call this function, you may have to do a
95 ;;; REOPTIMIZE-CONTINUATION to inform IR1 optimization that something
97 (declaim (ftype (function (node continuation) (values)) add-continuation-use))
98 (defun add-continuation-use (node cont)
99 (assert (not (node-cont node)))
100 (let ((block (continuation-block cont)))
101 (ecase (continuation-kind cont)
105 (let ((block (node-block node)))
107 (setf (continuation-block cont) block))
108 (setf (continuation-kind cont) :inside-block)
109 (setf (continuation-use cont) node))
110 ((:block-start :deleted-block-start)
111 (let ((uses (cons node (block-start-uses block))))
112 (setf (block-start-uses block) uses)
113 (setf (continuation-use cont)
114 (if (cdr uses) nil (car uses)))))))
115 (setf (node-cont node) cont)
118 ;;; Return true if Cont is the Node-Cont for Node and Cont is transferred to
119 ;;; immediately after the evaluation of Node.
120 (defun immediately-used-p (cont node)
121 (declare (type continuation cont) (type node node))
122 (and (eq (node-cont node) cont)
123 (not (eq (continuation-kind cont) :deleted))
124 (let ((cblock (continuation-block cont))
125 (nblock (node-block node)))
126 (or (eq cblock nblock)
127 (let ((succ (block-succ nblock)))
128 (and (= (length succ) 1)
129 (eq (first succ) cblock)))))))
131 ;;;; continuation substitution
133 ;;; In Old's Dest, replace Old with New. New's Dest must initially be NIL.
134 ;;; When we are done, we call Flush-Dest on Old to clear its Dest and to note
135 ;;; potential optimization opportunities.
136 (defun substitute-continuation (new old)
137 (declare (type continuation old new))
138 (assert (not (continuation-dest new)))
139 (let ((dest (continuation-dest old)))
142 (cif (setf (if-test dest) new))
143 (cset (setf (set-value dest) new))
144 (creturn (setf (return-result dest) new))
145 (exit (setf (exit-value dest) new))
147 (if (eq old (basic-combination-fun dest))
148 (setf (basic-combination-fun dest) new)
149 (setf (basic-combination-args dest)
150 (nsubst new old (basic-combination-args dest))))))
153 (setf (continuation-dest new) dest))
156 ;;; Replace all uses of OLD with uses of NEW, where NEW has an
157 ;;; arbitary number of uses. If NEW will end up with more than one
158 ;;; use, then we must arrange for it to start a block if it doesn't
160 (defun substitute-continuation-uses (new old)
161 (declare (type continuation old new))
162 (unless (and (eq (continuation-kind new) :unused)
163 (eq (continuation-kind old) :inside-block))
164 (ensure-block-start new))
167 (delete-continuation-use node)
168 (add-continuation-use node new))
169 (dolist (lexenv-use (continuation-lexenv-uses old))
170 (setf (cadr lexenv-use) new))
172 (reoptimize-continuation new)
175 ;;;; block starting/creation
177 ;;; Return the block that CONT is the start of, making a block if
178 ;;; necessary. This function is called by IR1 translators which may
179 ;;; cause a continuation to be used more than once. Every continuation
180 ;;; which may be used more than once must start a block by the time
181 ;;; that anyone does a USE-CONTINUATION on it.
183 ;;; We also throw the block into the next/prev list for the
184 ;;; *CURRENT-COMPONENT* so that we keep track of which blocks we have
186 (defun continuation-starts-block (cont)
187 (declare (type continuation cont))
188 (ecase (continuation-kind cont)
190 (assert (not (continuation-block cont)))
191 (let* ((head (component-head *current-component*))
192 (next (block-next head))
193 (new-block (make-block cont)))
194 (setf (block-next new-block) next)
195 (setf (block-prev new-block) head)
196 (setf (block-prev next) new-block)
197 (setf (block-next head) new-block)
198 (setf (continuation-block cont) new-block)
199 (setf (continuation-use cont) nil)
200 (setf (continuation-kind cont) :block-start)
203 (continuation-block cont))))
205 ;;; Ensure that Cont is the start of a block (or deleted) so that the use
206 ;;; set can be freely manipulated.
207 ;;; -- If the continuation is :Unused or is :Inside-Block and the Cont of Last
208 ;;; in its block, then we make it the start of a new deleted block.
209 ;;; -- If the continuation is :Inside-Block inside a block, then we split the
210 ;;; block using Node-Ends-Block, which makes the continuation be a
212 (defun ensure-block-start (cont)
213 (declare (type continuation cont))
214 (let ((kind (continuation-kind cont)))
216 ((:deleted :block-start :deleted-block-start))
217 ((:unused :inside-block)
218 (let ((block (continuation-block cont)))
219 (cond ((or (eq kind :unused)
220 (eq (node-cont (block-last block)) cont))
221 (setf (continuation-block cont)
222 (make-block-key :start cont
224 :start-uses (find-uses cont)))
225 (setf (continuation-kind cont) :deleted-block-start))
227 (node-ends-block (continuation-use cont))))))))
230 ;;;; miscellaneous shorthand functions
232 ;;; Return the home (i.e. enclosing non-let) lambda for Node. Since the
233 ;;; LEXENV-LAMBDA may be deleted, we must chain up the LAMBDA-CALL-LEXENV
234 ;;; thread until we find a lambda that isn't deleted, and then return its home.
235 (declaim (maybe-inline node-home-lambda))
236 (defun node-home-lambda (node)
237 (declare (type node node))
238 (do ((fun (lexenv-lambda (node-lexenv node))
239 (lexenv-lambda (lambda-call-lexenv fun))))
240 ((not (eq (functional-kind fun) :deleted))
242 (when (eq (lambda-home fun) fun)
245 #!-sb-fluid (declaim (inline node-block node-tlf-number))
246 (declaim (maybe-inline node-environment))
247 (defun node-block (node)
248 (declare (type node node))
249 (the cblock (continuation-block (node-prev node))))
250 (defun node-environment (node)
251 (declare (type node node))
252 #!-sb-fluid (declare (inline node-home-lambda))
253 (the environment (lambda-environment (node-home-lambda node))))
255 ;;; Return the enclosing cleanup for environment of the first or last node
257 (defun block-start-cleanup (block)
258 (declare (type cblock block))
259 (node-enclosing-cleanup (continuation-next (block-start block))))
260 (defun block-end-cleanup (block)
261 (declare (type cblock block))
262 (node-enclosing-cleanup (block-last block)))
264 ;;; Return the non-let lambda that holds Block's code.
265 (defun block-home-lambda (block)
266 (declare (type cblock block))
267 #!-sb-fluid (declare (inline node-home-lambda))
268 (node-home-lambda (block-last block)))
270 ;;; Return the IR1 environment for Block.
271 (defun block-environment (block)
272 (declare (type cblock block))
273 #!-sb-fluid (declare (inline node-home-lambda))
274 (lambda-environment (node-home-lambda (block-last block))))
276 ;;; Return the Top Level Form number of path, i.e. the ordinal number of
277 ;;; its orignal source's top-level form in its compilation unit.
278 (defun source-path-tlf-number (path)
279 (declare (list path))
282 ;;; Return the (reversed) list for the path in the orignal source (with the
283 ;;; TLF number last.)
284 (defun source-path-original-source (path)
285 (declare (list path) (inline member))
286 (cddr (member 'original-source-start path :test #'eq)))
288 ;;; Return the Form Number of Path's orignal source inside the Top Level
289 ;;; Form that contains it. This is determined by the order that we walk the
290 ;;; subforms of the top level source form.
291 (defun source-path-form-number (path)
292 (declare (list path) (inline member))
293 (cadr (member 'original-source-start path :test #'eq)))
295 ;;; Return a list of all the enclosing forms not in the original
296 ;;; source that converted to get to this form, with the immediate
297 ;;; source for node at the start of the list.
298 (defun source-path-forms (path)
299 (subseq path 0 (position 'original-source-start path)))
301 ;;; Return the innermost source form for Node.
302 (defun node-source-form (node)
303 (declare (type node node))
304 (let* ((path (node-source-path node))
305 (forms (source-path-forms path)))
308 (values (find-original-source path)))))
310 ;;; Return NODE-SOURCE-FORM, T if continuation has a single use,
311 ;;; otherwise NIL, NIL.
312 (defun continuation-source (cont)
313 (let ((use (continuation-use cont)))
315 (values (node-source-form use) t)
318 ;;; Return a new LEXENV just like DEFAULT except for the specified
319 ;;; slot values. Values for the alist slots are NCONCed to the
320 ;;; beginning of the current value, rather than replacing it entirely.
321 (defun make-lexenv (&key (default *lexenv*)
322 functions variables blocks tags type-restrictions
324 (lambda (lexenv-lambda default))
325 (cleanup (lexenv-cleanup default))
326 (policy (lexenv-policy default))
327 (interface-policy (lexenv-interface-policy default)))
328 (macrolet ((frob (var slot)
329 `(let ((old (,slot default)))
333 (internal-make-lexenv
334 (frob functions lexenv-functions)
335 (frob variables lexenv-variables)
336 (frob blocks lexenv-blocks)
337 (frob tags lexenv-tags)
338 (frob type-restrictions lexenv-type-restrictions)
339 lambda cleanup policy interface-policy
340 (frob options lexenv-options))))
342 ;;; Return a POLICY that defaults any unsupplied optimize qualities in
343 ;;; the INTERFACE-POLICY with the corresponding ones from the POLICY.
344 (defun make-interface-policy (lexenv)
345 (declare (type lexenv lexenv))
346 (let ((ipolicy (lexenv-interface-policy lexenv))
347 (policy (lexenv-policy lexenv)))
348 (let ((result policy))
349 (dolist (quality '(speed safety space))
350 (let ((iquality-entry (assoc quality ipolicy)))
352 (push iquality-entry result))))
355 ;;;; flow/DFO/component hackery
357 ;;; Join BLOCK1 and BLOCK2.
358 #!-sb-fluid (declaim (inline link-blocks))
359 (defun link-blocks (block1 block2)
360 (declare (type cblock block1 block2))
361 (setf (block-succ block1)
362 (if (block-succ block1)
363 (%link-blocks block1 block2)
365 (push block1 (block-pred block2))
367 (defun %link-blocks (block1 block2)
368 (declare (type cblock block1 block2) (inline member))
369 (let ((succ1 (block-succ block1)))
370 (assert (not (member block2 succ1 :test #'eq)))
371 (cons block2 succ1)))
373 ;;; Like LINK-BLOCKS, but we separate BLOCK1 and BLOCK2. If this leaves a
374 ;;; successor with a single predecessor that ends in an IF, then set
375 ;;; BLOCK-TEST-MODIFIED so that any test constraint will now be able to be
376 ;;; propagated to the successor.
377 (defun unlink-blocks (block1 block2)
378 (declare (type cblock block1 block2))
379 (let ((succ1 (block-succ block1)))
380 (if (eq block2 (car succ1))
381 (setf (block-succ block1) (cdr succ1))
382 (do ((succ (cdr succ1) (cdr succ))
384 ((eq (car succ) block2)
385 (setf (cdr prev) (cdr succ)))
388 (let ((new-pred (delq block1 (block-pred block2))))
389 (setf (block-pred block2) new-pred)
390 (when (and new-pred (null (rest new-pred)))
391 (let ((pred-block (first new-pred)))
392 (when (if-p (block-last pred-block))
393 (setf (block-test-modified pred-block) t)))))
396 ;;; Swing the succ/pred link between Block and Old to be between Block and
397 ;;; New. If Block ends in an IF, then we have to fix up the
398 ;;; consequent/alternative blocks to point to New. We also set
399 ;;; BLOCK-TEST-MODIFIED so that any test constraint will be applied to the new
401 (defun change-block-successor (block old new)
402 (declare (type cblock new old block) (inline member))
403 (unlink-blocks block old)
404 (let ((last (block-last block))
405 (comp (block-component block)))
406 (setf (component-reanalyze comp) t)
409 (setf (block-test-modified block) t)
410 (let* ((succ-left (block-succ block))
411 (new (if (and (eq new (component-tail comp))
415 (unless (member new succ-left :test #'eq)
416 (link-blocks block new))
417 (macrolet ((frob (slot)
418 `(when (eq (,slot last) old)
419 (setf (,slot last) new))))
421 (frob if-alternative))))
423 (unless (member new (block-succ block) :test #'eq)
424 (link-blocks block new)))))
428 ;;; Unlink a block from the next/prev chain. We also null out the
430 (declaim (ftype (function (cblock) (values)) remove-from-dfo))
431 #!-sb-fluid (declaim (inline remove-from-dfo))
432 (defun remove-from-dfo (block)
433 (let ((next (block-next block))
434 (prev (block-prev block)))
435 (setf (block-component block) nil)
436 (setf (block-next prev) next)
437 (setf (block-prev next) prev))
440 ;;; Add Block to the next/prev chain following After. We also set the
441 ;;; Component to be the same as for After.
442 #!-sb-fluid (declaim (inline add-to-dfo))
443 (defun add-to-dfo (block after)
444 (declare (type cblock block after))
445 (let ((next (block-next after))
446 (comp (block-component after)))
447 (assert (not (eq (component-kind comp) :deleted)))
448 (setf (block-component block) comp)
449 (setf (block-next after) block)
450 (setf (block-prev block) after)
451 (setf (block-next block) next)
452 (setf (block-prev next) block))
455 ;;; Set the Flag for all the blocks in Component to NIL, except for the head
456 ;;; and tail which are set to T.
457 (declaim (ftype (function (component) (values)) clear-flags))
458 (defun clear-flags (component)
459 (let ((head (component-head component))
460 (tail (component-tail component)))
461 (setf (block-flag head) t)
462 (setf (block-flag tail) t)
463 (do-blocks (block component)
464 (setf (block-flag block) nil)))
467 ;;; Make a component with no blocks in it. The Block-Flag is initially
468 ;;; true in the head and tail blocks.
469 (declaim (ftype (function nil component) make-empty-component))
470 (defun make-empty-component ()
471 (let* ((head (make-block-key :start nil :component nil))
472 (tail (make-block-key :start nil :component nil))
473 (res (make-component :head head :tail tail)))
474 (setf (block-flag head) t)
475 (setf (block-flag tail) t)
476 (setf (block-component head) res)
477 (setf (block-component tail) res)
478 (setf (block-next head) tail)
479 (setf (block-prev tail) head)
482 ;;; Makes Node the Last node in its block, splitting the block if necessary.
483 ;;; The new block is added to the DFO immediately following Node's block.
484 (defun node-ends-block (node)
485 (declare (type node node))
486 (let* ((block (node-block node))
487 (start (node-cont node))
488 (last (block-last block))
489 (last-cont (node-cont last)))
490 (unless (eq last node)
491 (assert (and (eq (continuation-kind start) :inside-block)
492 (not (block-delete-p block))))
493 (let* ((succ (block-succ block))
495 (make-block-key :start start
496 :component (block-component block)
497 :start-uses (list (continuation-use start))
498 :succ succ :last last)))
499 (setf (continuation-kind start) :block-start)
502 (cons new-block (remove block (block-pred b)))))
503 (setf (block-succ block) ())
504 (setf (block-last block) node)
505 (link-blocks block new-block)
506 (add-to-dfo new-block block)
507 (setf (component-reanalyze (block-component block)) t)
509 (do ((cont start (node-cont (continuation-next cont))))
511 (when (eq (continuation-kind last-cont) :inside-block)
512 (setf (continuation-block last-cont) new-block)))
513 (setf (continuation-block cont) new-block))
515 (setf (block-type-asserted block) t)
516 (setf (block-test-modified block) t))))
522 ;;; Deal with deleting the last (read) reference to a lambda-var. We
523 ;;; iterate over all local calls flushing the corresponding argument, allowing
524 ;;; the computation of the argument to be deleted. We also mark the let for
525 ;;; reoptimization, since it may be that we have deleted the last variable.
527 ;;; The lambda-var may still have some sets, but this doesn't cause too much
528 ;;; difficulty, since we can efficiently implement write-only variables. We
529 ;;; iterate over the sets, marking their blocks for dead code flushing, since
530 ;;; we can delete sets whose value is unused.
531 (defun delete-lambda-var (leaf)
532 (declare (type lambda-var leaf))
533 (let* ((fun (lambda-var-home leaf))
534 (n (position leaf (lambda-vars fun))))
535 (dolist (ref (leaf-refs fun))
536 (let* ((cont (node-cont ref))
537 (dest (continuation-dest cont)))
538 (when (and (combination-p dest)
539 (eq (basic-combination-fun dest) cont)
540 (eq (basic-combination-kind dest) :local))
541 (let* ((args (basic-combination-args dest))
543 (reoptimize-continuation arg)
545 (setf (elt args n) nil))))))
547 (dolist (set (lambda-var-sets leaf))
548 (setf (block-flush-p (node-block set)) t))
552 ;;; Note that something interesting has happened to Var. We only deal with
553 ;;; LET variables, marking the corresponding initial value arg as needing to be
555 (defun reoptimize-lambda-var (var)
556 (declare (type lambda-var var))
557 (let ((fun (lambda-var-home var)))
558 (when (and (eq (functional-kind fun) :let)
560 (do ((args (basic-combination-args
563 (first (leaf-refs fun)))))
565 (vars (lambda-vars fun) (cdr vars)))
567 (reoptimize-continuation (car args))))))
570 ;;; This function deletes functions that have no references. This need only
571 ;;; be called on functions that never had any references, since otherwise
572 ;;; DELETE-REF will handle the deletion.
573 (defun delete-functional (fun)
574 (assert (and (null (leaf-refs fun))
575 (not (functional-entry-function fun))))
577 (optional-dispatch (delete-optional-dispatch fun))
578 (clambda (delete-lambda fun)))
581 ;;; Deal with deleting the last reference to a lambda. Since there is only
582 ;;; one way into a lambda, deleting the last reference to a lambda ensures that
583 ;;; there is no way to reach any of the code in it. So we just set the
584 ;;; Functional-Kind for Fun and its Lets to :Deleted, causing IR1 optimization
585 ;;; to delete blocks in that lambda.
587 ;;; If the function isn't a Let, we unlink the function head and tail from
588 ;;; the component head and tail to indicate that the code is unreachable. We
589 ;;; also delete the function from Component-Lambdas (it won't be there before
590 ;;; local call analysis, but no matter.) If the lambda was never referenced,
593 ;;; If the lambda is an XEP, then we null out the Entry-Function in its
594 ;;; Entry-Function so that people will know that it is not an entry point
596 (defun delete-lambda (leaf)
597 (declare (type clambda leaf))
598 (let ((kind (functional-kind leaf))
599 (bind (lambda-bind leaf)))
600 (assert (not (member kind '(:deleted :optional :top-level))))
601 (setf (functional-kind leaf) :deleted)
602 (setf (lambda-bind leaf) nil)
603 (dolist (let (lambda-lets leaf))
604 (setf (lambda-bind let) nil)
605 (setf (functional-kind let) :deleted))
607 (if (member kind '(:let :mv-let :assignment))
608 (let ((home (lambda-home leaf)))
609 (setf (lambda-lets home) (delete leaf (lambda-lets home))))
610 (let* ((bind-block (node-block bind))
611 (component (block-component bind-block))
612 (return (lambda-return leaf)))
613 (assert (null (leaf-refs leaf)))
614 (unless (leaf-ever-used leaf)
615 (let ((*compiler-error-context* bind))
616 (compiler-note "deleting unused function~:[.~;~:*~% ~S~]"
618 (unlink-blocks (component-head component) bind-block)
620 (unlink-blocks (node-block return) (component-tail component)))
621 (setf (component-reanalyze component) t)
622 (let ((tails (lambda-tail-set leaf)))
623 (setf (tail-set-functions tails)
624 (delete leaf (tail-set-functions tails)))
625 (setf (lambda-tail-set leaf) nil))
626 (setf (component-lambdas component)
627 (delete leaf (component-lambdas component)))))
629 (when (eq kind :external)
630 (let ((fun (functional-entry-function leaf)))
631 (setf (functional-entry-function fun) nil)
632 (when (optional-dispatch-p fun)
633 (delete-optional-dispatch fun)))))
637 ;;; Deal with deleting the last reference to an Optional-Dispatch. We have
638 ;;; to be a bit more careful than with lambdas, since Delete-Ref is used both
639 ;;; before and after local call analysis. Afterward, all references to
640 ;;; still-existing optional-dispatches have been moved to the XEP, leaving it
641 ;;; with no references at all. So we look at the XEP to see whether an
642 ;;; optional-dispatch is still really being used. But before local call
643 ;;; analysis, there are no XEPs, and all references are direct.
645 ;;; When we do delete the optional-dispatch, we grovel all of its
646 ;;; entry-points, making them be normal lambdas, and then deleting the ones
647 ;;; with no references. This deletes any e-p lambdas that were either never
648 ;;; referenced, or couldn't be deleted when the last deference was deleted (due
649 ;;; to their :OPTIONAL kind.)
651 ;;; Note that the last optional ep may alias the main entry, so when we process
652 ;;; the main entry, its kind may have been changed to NIL or even converted to
654 (defun delete-optional-dispatch (leaf)
655 (declare (type optional-dispatch leaf))
656 (let ((entry (functional-entry-function leaf)))
657 (unless (and entry (leaf-refs entry))
658 (assert (or (not entry) (eq (functional-kind entry) :deleted)))
659 (setf (functional-kind leaf) :deleted)
662 (unless (eq (functional-kind fun) :deleted)
663 (assert (eq (functional-kind fun) :optional))
664 (setf (functional-kind fun) nil)
665 (let ((refs (leaf-refs fun)))
669 (or (maybe-let-convert fun)
670 (maybe-convert-to-assignment fun)))
672 (maybe-convert-to-assignment fun)))))))
674 (dolist (ep (optional-dispatch-entry-points leaf))
676 (when (optional-dispatch-more-entry leaf)
677 (frob (optional-dispatch-more-entry leaf)))
678 (let ((main (optional-dispatch-main-entry leaf)))
679 (when (eq (functional-kind main) :optional)
684 ;;; Do stuff to delete the semantic attachments of a Ref node. When this
685 ;;; leaves zero or one reference, we do a type dispatch off of the leaf to
686 ;;; determine if a special action is appropriate.
687 (defun delete-ref (ref)
688 (declare (type ref ref))
689 (let* ((leaf (ref-leaf ref))
690 (refs (delete ref (leaf-refs leaf))))
691 (setf (leaf-refs leaf) refs)
695 (lambda-var (delete-lambda-var leaf))
697 (ecase (functional-kind leaf)
698 ((nil :let :mv-let :assignment :escape :cleanup)
699 (assert (not (functional-entry-function leaf)))
700 (delete-lambda leaf))
702 (delete-lambda leaf))
703 ((:deleted :optional))))
705 (unless (eq (functional-kind leaf) :deleted)
706 (delete-optional-dispatch leaf)))))
709 (clambda (or (maybe-let-convert leaf)
710 (maybe-convert-to-assignment leaf)))
711 (lambda-var (reoptimize-lambda-var leaf))))
714 (clambda (maybe-convert-to-assignment leaf))))))
718 ;;; This function is called by people who delete nodes; it provides a way to
719 ;;; indicate that the value of a continuation is no longer used. We null out
720 ;;; the Continuation-Dest, set Flush-P in the blocks containing uses of Cont
721 ;;; and set Component-Reoptimize. If the Prev of the use is deleted, then we
722 ;;; blow off reoptimization.
724 ;;; If the continuation is :Deleted, then we don't do anything, since all
725 ;;; semantics have already been flushed. :Deleted-Block-Start start
726 ;;; continuations are treated just like :Block-Start; it is possible that the
727 ;;; continuation may be given a new dest (e.g. by SUBSTITUTE-CONTINUATION), so
728 ;;; we don't want to delete it.
729 (defun flush-dest (cont)
730 (declare (type continuation cont))
732 (unless (eq (continuation-kind cont) :deleted)
733 (assert (continuation-dest cont))
734 (setf (continuation-dest cont) nil)
736 (let ((prev (node-prev use)))
737 (unless (eq (continuation-kind prev) :deleted)
738 (let ((block (continuation-block prev)))
739 (setf (component-reoptimize (block-component block)) t)
740 (setf (block-attributep (block-flags block) flush-p type-asserted)
743 (setf (continuation-%type-check cont) nil)
747 ;;; Do a graph walk backward from Block, marking all predecessor blocks with
748 ;;; the DELETE-P flag.
749 (defun mark-for-deletion (block)
750 (declare (type cblock block))
751 (unless (block-delete-p block)
752 (setf (block-delete-p block) t)
753 (setf (component-reanalyze (block-component block)) t)
754 (dolist (pred (block-pred block))
755 (mark-for-deletion pred)))
758 ;;; Delete Cont, eliminating both control and value semantics. We set
759 ;;; FLUSH-P and COMPONENT-REOPTIMIZE similarly to in FLUSH-DEST. Here we must
760 ;;; get the component from the use block, since the continuation may be a
761 ;;; :DELETED-BLOCK-START.
763 ;;; If Cont has DEST, then it must be the case that the DEST is unreachable,
764 ;;; since we can't compute the value desired. In this case, we call
765 ;;; MARK-FOR-DELETION to cause the DEST block and its predecessors to tell
766 ;;; people to ignore them, and to cause them to be deleted eventually.
767 (defun delete-continuation (cont)
768 (declare (type continuation cont))
769 (assert (not (eq (continuation-kind cont) :deleted)))
772 (let ((prev (node-prev use)))
773 (unless (eq (continuation-kind prev) :deleted)
774 (let ((block (continuation-block prev)))
775 (setf (block-attributep (block-flags block) flush-p type-asserted) t)
776 (setf (component-reoptimize (block-component block)) t)))))
778 (let ((dest (continuation-dest cont)))
780 (let ((prev (node-prev dest)))
782 (not (eq (continuation-kind prev) :deleted)))
783 (let ((block (continuation-block prev)))
784 (unless (block-delete-p block)
785 (mark-for-deletion block)))))))
787 (setf (continuation-kind cont) :deleted)
788 (setf (continuation-dest cont) nil)
789 (setf (continuation-next cont) nil)
790 (setf (continuation-asserted-type cont) *empty-type*)
791 (setf (continuation-%derived-type cont) *empty-type*)
792 (setf (continuation-use cont) nil)
793 (setf (continuation-block cont) nil)
794 (setf (continuation-reoptimize cont) nil)
795 (setf (continuation-%type-check cont) nil)
796 (setf (continuation-info cont) nil)
800 ;;; This function does what is necessary to eliminate the code in it from
801 ;;; the IR1 representation. This involves unlinking it from its predecessors
802 ;;; and successors and deleting various node-specific semantic information.
804 ;;; We mark the Start as has having no next and remove the last node from
805 ;;; its Cont's uses. We also flush the DEST for all continuations whose values
806 ;;; are received by nodes in the block.
807 (defun delete-block (block)
808 (declare (type cblock block))
809 (assert (block-component block) () "Block is already deleted.")
810 (note-block-deletion block)
811 (setf (block-delete-p block) t)
813 (let* ((last (block-last block))
814 (cont (node-cont last)))
815 (delete-continuation-use last)
816 (if (eq (continuation-kind cont) :unused)
817 (delete-continuation cont)
818 (reoptimize-continuation cont)))
820 (dolist (b (block-pred block))
821 (unlink-blocks b block))
822 (dolist (b (block-succ block))
823 (unlink-blocks block b))
825 (do-nodes (node cont block)
827 (ref (delete-ref node))
829 (flush-dest (if-test node)))
830 ;; The next two cases serve to maintain the invariant that a LET always
831 ;; has a well-formed COMBINATION, REF and BIND. We delete the lambda
832 ;; whenever we delete any of these, but we must be careful that this LET
833 ;; has not already been partially deleted.
835 (when (and (eq (basic-combination-kind node) :local)
836 ;; Guards COMBINATION-LAMBDA agains the REF being deleted.
837 (continuation-use (basic-combination-fun node)))
838 (let ((fun (combination-lambda node)))
839 ;; If our REF was the 2'nd to last ref, and has been deleted, then
840 ;; Fun may be a LET for some other combination.
841 (when (and (member (functional-kind fun) '(:let :mv-let))
842 (eq (let-combination fun) node))
843 (delete-lambda fun))))
844 (flush-dest (basic-combination-fun node))
845 (dolist (arg (basic-combination-args node))
846 (when arg (flush-dest arg))))
848 (let ((lambda (bind-lambda node)))
849 (unless (eq (functional-kind lambda) :deleted)
850 (assert (member (functional-kind lambda)
851 '(:let :mv-let :assignment)))
852 (delete-lambda lambda))))
854 (let ((value (exit-value node))
855 (entry (exit-entry node)))
859 (setf (entry-exits entry)
860 (delete node (entry-exits entry))))))
862 (flush-dest (return-result node))
863 (delete-return node))
865 (flush-dest (set-value node))
866 (let ((var (set-var node)))
867 (setf (basic-var-sets var)
868 (delete node (basic-var-sets var))))))
870 (delete-continuation (node-prev node)))
872 (remove-from-dfo block)
875 ;;; Do stuff to indicate that the return node Node is being deleted. We set
876 ;;; the RETURN to NIL.
877 (defun delete-return (node)
878 (declare (type creturn node))
879 (let ((fun (return-lambda node)))
880 (assert (lambda-return fun))
881 (setf (lambda-return fun) nil))
884 ;;; If any of the Vars in fun were never referenced and was not declared
885 ;;; IGNORE, then complain.
886 (defun note-unreferenced-vars (fun)
887 (declare (type clambda fun))
888 (dolist (var (lambda-vars fun))
889 (unless (or (leaf-ever-used var)
890 (lambda-var-ignorep var))
891 (let ((*compiler-error-context* (lambda-bind fun)))
892 (unless (policy *compiler-error-context* (= inhibit-warnings 3))
893 ;; ANSI section "3.2.5 Exceptional Situations in the Compiler"
894 ;; requires this to be a STYLE-WARNING.
895 (compiler-style-warning "The variable ~S is defined but never used."
897 (setf (leaf-ever-used var) t))))
900 (defvar *deletion-ignored-objects* '(t nil))
902 ;;; Return true if we can find Obj in Form, NIL otherwise. We bound our
903 ;;; recursion so that we don't get lost in circular structures. We ignore the
904 ;;; car of forms if they are a symbol (to prevent confusing function
905 ;;; referencess with variables), and we also ignore anything inside ' or #'.
906 (defun present-in-form (obj form depth)
907 (declare (type (integer 0 20) depth))
908 (cond ((= depth 20) nil)
912 (let ((first (car form))
914 (if (member first '(quote function))
916 (or (and (not (symbolp first))
917 (present-in-form obj first depth))
918 (do ((l (cdr form) (cdr l))
920 ((or (atom l) (> n 100))
923 (when (present-in-form obj (car l) depth)
926 ;;; This function is called on a block immediately before we delete it. We
927 ;;; check to see whether any of the code about to die appeared in the original
928 ;;; source, and emit a note if so.
930 ;;; If the block was in a lambda is now deleted, then we ignore the whole
931 ;;; block, since this case is picked off in DELETE-LAMBDA. We also ignore
932 ;;; the deletion of CRETURN nodes, since it is somewhat reasonable for a
933 ;;; function to not return, and there is a different note for that case anyway.
935 ;;; If the actual source is an atom, then we use a bunch of heuristics to
936 ;;; guess whether this reference really appeared in the original source:
937 ;;; -- If a symbol, it must be interned and not a keyword.
938 ;;; -- It must not be an easily introduced constant (T or NIL, a fixnum or a
940 ;;; -- The atom must be "present" in the original source form, and present in
941 ;;; all intervening actual source forms.
942 (defun note-block-deletion (block)
943 (let ((home (block-home-lambda block)))
944 (unless (eq (functional-kind home) :deleted)
945 (do-nodes (node cont block)
946 (let* ((path (node-source-path node))
947 (first (first path)))
948 (when (or (eq first 'original-source-start)
950 (or (not (symbolp first))
951 (let ((pkg (symbol-package first)))
953 (not (eq pkg (symbol-package :end))))))
954 (not (member first *deletion-ignored-objects*))
955 (not (typep first '(or fixnum character)))
957 (present-in-form first x 0))
958 (source-path-forms path))
959 (present-in-form first (find-original-source path)
961 (unless (return-p node)
962 (let ((*compiler-error-context* node))
963 (compiler-note "deleting unreachable code")))
967 ;;; Delete a node from a block, deleting the block if there are no nodes
968 ;;; left. We remove the node from the uses of its CONT, but we don't deal with
969 ;;; cleaning up any type-specific semantic attachments. If the CONT is :UNUSED
970 ;;; after deleting this use, then we delete CONT. (Note :UNUSED is not the
971 ;;; same as no uses. A continuation will only become :UNUSED if it was
972 ;;; :INSIDE-BLOCK before.)
974 ;;; If the node is the last node, there must be exactly one successor. We
975 ;;; link all of our precedessors to the successor and unlink the block. In
976 ;;; this case, we return T, otherwise NIL. If no nodes are left, and the block
977 ;;; is a successor of itself, then we replace the only node with a degenerate
978 ;;; exit node. This provides a way to represent the bodyless infinite loop,
979 ;;; given the prohibition on empty blocks in IR1.
980 (defun unlink-node (node)
981 (declare (type node node))
982 (let* ((cont (node-cont node))
983 (next (continuation-next cont))
984 (prev (node-prev node))
985 (block (continuation-block prev))
986 (prev-kind (continuation-kind prev))
987 (last (block-last block)))
989 (unless (eq (continuation-kind cont) :deleted)
990 (delete-continuation-use node)
991 (when (eq (continuation-kind cont) :unused)
992 (assert (not (continuation-dest cont)))
993 (delete-continuation cont)))
995 (setf (block-type-asserted block) t)
996 (setf (block-test-modified block) t)
998 (cond ((or (eq prev-kind :inside-block)
999 (and (eq prev-kind :block-start)
1000 (not (eq node last))))
1001 (cond ((eq node last)
1002 (setf (block-last block) (continuation-use prev))
1003 (setf (continuation-next prev) nil))
1005 (setf (continuation-next prev) next)
1006 (setf (node-prev next) prev)))
1007 (setf (node-prev node) nil)
1010 (assert (eq prev-kind :block-start))
1011 (assert (eq node last))
1012 (let* ((succ (block-succ block))
1013 (next (first succ)))
1014 (assert (and succ (null (cdr succ))))
1016 ((member block succ)
1017 (with-ir1-environment node
1018 (let ((exit (make-exit))
1019 (dummy (make-continuation)))
1020 (setf (continuation-next prev) nil)
1021 (prev-link exit prev)
1022 (add-continuation-use exit dummy)
1023 (setf (block-last block) exit)))
1024 (setf (node-prev node) nil)
1027 (assert (eq (block-start-cleanup block)
1028 (block-end-cleanup block)))
1029 (unlink-blocks block next)
1030 (dolist (pred (block-pred block))
1031 (change-block-successor pred block next))
1032 (remove-from-dfo block)
1033 (cond ((continuation-dest prev)
1034 (setf (continuation-next prev) nil)
1035 (setf (continuation-kind prev) :deleted-block-start))
1037 (delete-continuation prev)))
1038 (setf (node-prev node) nil)
1041 ;;; Return true if NODE has been deleted, false if it is still a valid part
1043 (defun node-deleted (node)
1044 (declare (type node node))
1045 (let ((prev (node-prev node)))
1047 (not (eq (continuation-kind prev) :deleted))
1048 (let ((block (continuation-block prev)))
1049 (and (block-component block)
1050 (not (block-delete-p block))))))))
1052 ;;; Delete all the blocks and functions in Component. We scan first marking
1053 ;;; the blocks as delete-p to prevent weird stuff from being triggered by
1055 (defun delete-component (component)
1056 (declare (type component component))
1057 (assert (null (component-new-functions component)))
1058 (setf (component-kind component) :deleted)
1059 (do-blocks (block component)
1060 (setf (block-delete-p block) t))
1061 (dolist (fun (component-lambdas component))
1062 (setf (functional-kind fun) nil)
1063 (setf (functional-entry-function fun) nil)
1064 (setf (leaf-refs fun) nil)
1065 (delete-functional fun))
1066 (do-blocks (block component)
1067 (delete-block block))
1070 ;;; Convert code of the form
1071 ;;; (FOO ... (FUN ...) ...)
1073 ;;; (FOO ... ... ...).
1074 ;;; In other words, replace the function combination FUN by its
1075 ;;; arguments. If there are any problems with doing this, use GIVE-UP
1076 ;;; to blow out of whatever transform called this. Note, as the number
1077 ;;; of arguments changes, the transform must be prepared to return a
1078 ;;; lambda with a new lambda-list with the correct number of
1080 (defun extract-function-args (cont fun num-args)
1082 "If CONT is a call to FUN with NUM-ARGS args, change those arguments
1083 to feed directly to the continuation-dest of CONT, which must be
1085 (declare (type continuation cont)
1087 (type index num-args))
1088 (let ((outside (continuation-dest cont))
1089 (inside (continuation-use cont)))
1090 (assert (combination-p outside))
1091 (unless (combination-p inside)
1092 (give-up-ir1-transform))
1093 (let ((inside-fun (combination-fun inside)))
1094 (unless (eq (continuation-function-name inside-fun) fun)
1095 (give-up-ir1-transform))
1096 (let ((inside-args (combination-args inside)))
1097 (unless (= (length inside-args) num-args)
1098 (give-up-ir1-transform))
1099 (let* ((outside-args (combination-args outside))
1100 (arg-position (position cont outside-args))
1101 (before-args (subseq outside-args 0 arg-position))
1102 (after-args (subseq outside-args (1+ arg-position))))
1103 (dolist (arg inside-args)
1104 (setf (continuation-dest arg) outside))
1105 (setf (combination-args inside) nil)
1106 (setf (combination-args outside)
1107 (append before-args inside-args after-args))
1108 (change-ref-leaf (continuation-use inside-fun)
1109 (find-free-function 'list "???"))
1110 (setf (combination-kind inside) :full)
1111 (setf (node-derived-type inside) *wild-type*)
1113 (setf (continuation-asserted-type cont) *wild-type*)
1118 ;;; Change the Leaf that a Ref refers to.
1119 (defun change-ref-leaf (ref leaf)
1120 (declare (type ref ref) (type leaf leaf))
1121 (unless (eq (ref-leaf ref) leaf)
1122 (push ref (leaf-refs leaf))
1124 (setf (ref-leaf ref) leaf)
1125 (let ((ltype (leaf-type leaf)))
1126 (if (function-type-p ltype)
1127 (setf (node-derived-type ref) ltype)
1128 (derive-node-type ref ltype)))
1129 (reoptimize-continuation (node-cont ref)))
1132 ;;; Change all Refs for Old-Leaf to New-Leaf.
1133 (defun substitute-leaf (new-leaf old-leaf)
1134 (declare (type leaf new-leaf old-leaf))
1135 (dolist (ref (leaf-refs old-leaf))
1136 (change-ref-leaf ref new-leaf))
1139 ;;; Like SUBSITIUTE-LEAF, only there is a predicate on the Ref to tell
1140 ;;; whether to substitute.
1141 (defun substitute-leaf-if (test new-leaf old-leaf)
1142 (declare (type leaf new-leaf old-leaf) (type function test))
1143 (dolist (ref (leaf-refs old-leaf))
1144 (when (funcall test ref)
1145 (change-ref-leaf ref new-leaf)))
1148 ;;; Return a LEAF which represents the specified constant object. If the
1149 ;;; object is not in *CONSTANTS*, then we create a new constant LEAF and
1151 #!-sb-fluid (declaim (maybe-inline find-constant))
1152 (defun find-constant (object)
1153 (if (typep object '(or symbol number character instance))
1154 (or (gethash object *constants*)
1155 (setf (gethash object *constants*)
1156 (make-constant :value object
1158 :type (ctype-of object)
1159 :where-from :defined)))
1160 (make-constant :value object
1162 :type (ctype-of object)
1163 :where-from :defined)))
1165 ;;; If there is a non-local exit noted in Entry's environment that exits to
1166 ;;; Cont in that entry, then return it, otherwise return NIL.
1167 (defun find-nlx-info (entry cont)
1168 (declare (type entry entry) (type continuation cont))
1169 (let ((entry-cleanup (entry-cleanup entry)))
1170 (dolist (nlx (environment-nlx-info (node-environment entry)) nil)
1171 (when (and (eq (nlx-info-continuation nlx) cont)
1172 (eq (nlx-info-cleanup nlx) entry-cleanup))
1175 ;;;; functional hackery
1177 ;;; If Functional is a Lambda, just return it; if it is an
1178 ;;; optional-dispatch, return the main-entry.
1179 (declaim (ftype (function (functional) clambda) main-entry))
1180 (defun main-entry (functional)
1181 (etypecase functional
1182 (clambda functional)
1184 (optional-dispatch-main-entry functional))))
1186 ;;; Returns true if Functional is a thing that can be treated like
1187 ;;; MV-Bind when it appears in an MV-Call. All fixed arguments must be
1188 ;;; optional with null default and no supplied-p. There must be a rest
1189 ;;; arg with no references.
1190 (declaim (ftype (function (functional) boolean) looks-like-an-mv-bind))
1191 (defun looks-like-an-mv-bind (functional)
1192 (and (optional-dispatch-p functional)
1193 (do ((arg (optional-dispatch-arglist functional) (cdr arg)))
1195 (let ((info (lambda-var-arg-info (car arg))))
1196 (unless info (return nil))
1197 (case (arg-info-kind info)
1199 (when (or (arg-info-supplied-p info) (arg-info-default info))
1202 (return (and (null (cdr arg)) (null (leaf-refs (car arg))))))
1206 ;;; Return true if function is an XEP. This is true of normal XEPs
1207 ;;; (:External kind) and top-level lambdas (:Top-Level kind.)
1208 #!-sb-fluid (declaim (inline external-entry-point-p))
1209 (defun external-entry-point-p (fun)
1210 (declare (type functional fun))
1211 (not (null (member (functional-kind fun) '(:external :top-level)))))
1213 ;;; If Cont's only use is a non-notinline global function reference, then
1214 ;;; return the referenced symbol, otherwise NIL. If Notinline-OK is true, then
1215 ;;; we don't care if the leaf is notinline.
1216 (defun continuation-function-name (cont &optional notinline-ok)
1217 (declare (type continuation cont))
1218 (let ((use (continuation-use cont)))
1220 (let ((leaf (ref-leaf use)))
1221 (if (and (global-var-p leaf)
1222 (eq (global-var-kind leaf) :global-function)
1223 (or (not (defined-function-p leaf))
1224 (not (eq (defined-function-inlinep leaf) :notinline))
1230 ;;; Return the COMBINATION node that is the call to the let Fun.
1231 (defun let-combination (fun)
1232 (declare (type clambda fun))
1233 (assert (member (functional-kind fun) '(:let :mv-let)))
1234 (continuation-dest (node-cont (first (leaf-refs fun)))))
1236 ;;; Return the initial value continuation for a let variable or NIL if none.
1237 (defun let-var-initial-value (var)
1238 (declare (type lambda-var var))
1239 (let ((fun (lambda-var-home var)))
1240 (elt (combination-args (let-combination fun))
1241 (position-or-lose var (lambda-vars fun)))))
1243 ;;; Return the LAMBDA that is called by the local Call.
1244 #!-sb-fluid (declaim (inline combination-lambda))
1245 (defun combination-lambda (call)
1246 (declare (type basic-combination call))
1247 (assert (eq (basic-combination-kind call) :local))
1248 (ref-leaf (continuation-use (basic-combination-fun call))))
1250 (defvar *inline-expansion-limit* 200
1252 "An upper limit on the number of inline function calls that will be expanded
1253 in any given code object (single function or block compilation.)")
1255 ;;; Check whether Node's component has exceeded its inline expansion
1256 ;;; limit, and warn if so, returning NIL.
1257 (defun inline-expansion-ok (node)
1258 (let ((expanded (incf (component-inline-expansions
1260 (node-block node))))))
1261 (cond ((> expanded *inline-expansion-limit*) nil)
1262 ((= expanded *inline-expansion-limit*)
1263 (let ((*compiler-error-context* node))
1264 (compiler-note "*INLINE-EXPANSION-LIMIT* (~D) was exceeded, ~
1265 probably trying to~% ~
1266 inline a recursive function."
1267 *inline-expansion-limit*))
1271 ;;;; compiler error context determination
1273 (declaim (special *current-path*))
1275 ;;; We bind print level and length when printing out messages so that
1276 ;;; we don't dump huge amounts of garbage.
1278 ;;; FIXME: It's not possible to get the defaults right for everyone.
1279 ;;; So: Should these variables be in the SB-EXT package? Or should we
1280 ;;; just get rid of them completely and just use the bare
1281 ;;; CL:*PRINT-FOO* variables instead?
1282 (declaim (type (or unsigned-byte null)
1283 *compiler-error-print-level*
1284 *compiler-error-print-length*
1285 *compiler-error-print-lines*))
1286 (defvar *compiler-error-print-level* 5
1288 "the value for *PRINT-LEVEL* when printing compiler error messages")
1289 (defvar *compiler-error-print-length* 10
1291 "the value for *PRINT-LENGTH* when printing compiler error messages")
1292 (defvar *compiler-error-print-lines* 12
1294 "the value for *PRINT-LINES* when printing compiler error messages")
1296 (defvar *enclosing-source-cutoff* 1
1298 "The maximum number of enclosing non-original source forms (i.e. from
1299 macroexpansion) that we print in full. For additional enclosing forms, we
1300 print only the CAR.")
1301 (declaim (type unsigned-byte *enclosing-source-cutoff*))
1303 ;;; We separate the determination of compiler error contexts from the actual
1304 ;;; signalling of those errors by objectifying the error context. This allows
1305 ;;; postponement of the determination of how (and if) to signal the error.
1307 ;;; We take care not to reference any of the IR1 so that pending potential
1308 ;;; error messages won't prevent the IR1 from being GC'd. To this end, we
1309 ;;; convert source forms to strings so that source forms that contain IR1
1310 ;;; references (e.g. %DEFUN) don't hold onto the IR.
1311 (defstruct (compiler-error-context
1312 #-no-ansi-print-object
1313 (:print-object (lambda (x stream)
1314 (print-unreadable-object (x stream :type t)))))
1315 ;; A list of the stringified CARs of the enclosing non-original source forms
1316 ;; exceeding the *enclosing-source-cutoff*.
1317 (enclosing-source nil :type list)
1318 ;; A list of stringified enclosing non-original source forms.
1319 (source nil :type list)
1320 ;; The stringified form in the original source that expanded into Source.
1321 (original-source (required-argument) :type simple-string)
1322 ;; A list of prefixes of "interesting" forms that enclose original-source.
1323 (context nil :type list)
1324 ;; The FILE-INFO-NAME for the relevant FILE-INFO.
1325 (file-name (required-argument)
1326 :type (or pathname (member :lisp :stream)))
1327 ;; The file position at which the top-level form starts, if applicable.
1328 (file-position nil :type (or index null))
1329 ;; The original source part of the source path.
1330 (original-source-path nil :type list))
1332 ;;; If true, this is the node which is used as context in compiler warning
1334 (declaim (type (or null compiler-error-context node) *compiler-error-context*))
1335 (defvar *compiler-error-context* nil)
1337 ;;; a hashtable mapping macro names to source context parsers. Each parser
1338 ;;; function returns the source-context list for that form.
1339 (defvar *source-context-methods* (make-hash-table))
1341 ;;; documentation originally from cmu-user.tex:
1342 ;;; This macro defines how to extract an abbreviated source context from
1343 ;;; the \var{name}d form when it appears in the compiler input.
1344 ;;; \var{lambda-list} is a \code{defmacro} style lambda-list used to
1345 ;;; parse the arguments. The \var{body} should return a list of
1346 ;;; subforms that can be printed on about one line. There are
1347 ;;; predefined methods for \code{defstruct}, \code{defmethod}, etc. If
1348 ;;; no method is defined, then the first two subforms are returned.
1349 ;;; Note that this facility implicitly determines the string name
1350 ;;; associated with anonymous functions.
1351 ;;; So even though SBCL itself only uses this macro within this file, it's a
1352 ;;; reasonable thing to put in SB-EXT in case some dedicated user wants to do
1353 ;;; some heavy tweaking to make SBCL give more informative output about his
1355 (defmacro def-source-context (name lambda-list &body body)
1357 "DEF-SOURCE-CONTEXT Name Lambda-List Form*
1358 This macro defines how to extract an abbreviated source context from the
1359 Named form when it appears in the compiler input. Lambda-List is a DEFMACRO
1360 style lambda-list used to parse the arguments. The Body should return a
1361 list of subforms suitable for a \"~{~S ~}\" format string."
1362 (let ((n-whole (gensym)))
1363 `(setf (gethash ',name *source-context-methods*)
1364 #'(lambda (,n-whole)
1365 (destructuring-bind ,lambda-list ,n-whole ,@body)))))
1367 (def-source-context defstruct (name-or-options &rest slots)
1368 (declare (ignore slots))
1369 `(defstruct ,(if (consp name-or-options)
1370 (car name-or-options)
1373 (def-source-context function (thing)
1374 (if (and (consp thing) (eq (first thing) 'lambda) (consp (rest thing)))
1375 `(lambda ,(second thing))
1376 `(function ,thing)))
1378 ;;; Return the first two elements of FORM if FORM is a list. Take the
1379 ;;; CAR of the second form if appropriate.
1380 (defun source-form-context (form)
1381 (cond ((atom form) nil)
1382 ((>= (length form) 2)
1383 (funcall (gethash (first form) *source-context-methods*
1385 (declare (ignore x))
1386 (list (first form) (second form))))
1391 ;;; Given a source path, return the original source form and a description
1392 ;;; of the interesting aspects of the context in which it appeared. The
1393 ;;; context is a list of lists, one sublist per context form. The sublist is a
1394 ;;; list of some of the initial subforms of the context form.
1396 ;;; For now, we use the first two subforms of each interesting form. A form is
1397 ;;; interesting if the first element is a symbol beginning with "DEF" and it is
1398 ;;; not the source form. If there is no DEF-mumble, then we use the outermost
1399 ;;; containing form. If the second subform is a list, then in some cases we
1400 ;;; return the car of that form rather than the whole form (i.e. don't show
1401 ;;; defstruct options, etc.)
1402 (defun find-original-source (path)
1403 (declare (list path))
1404 (let* ((rpath (reverse (source-path-original-source path)))
1406 (root (find-source-root tlf *source-info*)))
1407 (collect ((context))
1409 (current (rest rpath)))
1412 (assert (null current))
1414 (let ((head (first form)))
1415 (when (symbolp head)
1416 (let ((name (symbol-name head)))
1417 (when (and (>= (length name) 3) (string= name "DEF" :end1 3))
1418 (context (source-form-context form))))))
1419 (when (null current) (return))
1420 (setq form (nth (pop current) form)))
1423 (values form (context)))
1425 (let ((c (source-form-context root)))
1426 (values form (if c (list c) nil))))
1428 (values '(unable to locate source)
1429 '((some strange place)))))))))
1431 ;;; Convert a source form to a string, suitably formatted for use in
1432 ;;; compiler warnings.
1433 (defun stringify-form (form &optional (pretty t))
1434 (let ((*print-level* *compiler-error-print-level*)
1435 (*print-length* *compiler-error-print-length*)
1436 (*print-lines* *compiler-error-print-lines*)
1437 (*print-pretty* pretty))
1439 (format nil "~<~@; ~S~:>" (list form))
1440 (prin1-to-string form))))
1442 ;;; Return a COMPILER-ERROR-CONTEXT structure describing the current
1443 ;;; error context, or NIL if we can't figure anything out. ARGS is a
1444 ;;; list of things that are going to be printed out in the error
1445 ;;; message, and can thus be blown off when they appear in the source
1447 (defun find-error-context (args)
1448 (let ((context *compiler-error-context*))
1449 (if (compiler-error-context-p context)
1451 (let ((path (or *current-path*
1453 (node-source-path context)
1455 (when (and *source-info* path)
1456 (multiple-value-bind (form src-context) (find-original-source path)
1457 (collect ((full nil cons)
1459 (let ((forms (source-path-forms path))
1461 (dolist (src (if (member (first forms) args)
1464 (if (>= n *enclosing-source-cutoff*)
1465 (short (stringify-form (if (consp src)
1469 (full (stringify-form src)))
1472 (let* ((tlf (source-path-tlf-number path))
1473 (file (find-file-info tlf *source-info*)))
1474 (make-compiler-error-context
1475 :enclosing-source (short)
1477 :original-source (stringify-form form)
1478 :context src-context
1479 :file-name (file-info-name file)
1481 (multiple-value-bind (ignore pos)
1482 (find-source-root tlf *source-info*)
1483 (declare (ignore ignore))
1485 :original-source-path
1486 (source-path-original-source path))))))))))
1488 ;;;; printing error messages
1490 ;;; We save the context information that we printed out most recently
1491 ;;; so that we don't print it out redundantly.
1493 ;;; The last COMPILER-ERROR-CONTEXT that we printed.
1494 (defvar *last-error-context* nil)
1495 (declaim (type (or compiler-error-context null) *last-error-context*))
1497 ;;; The format string and args for the last error we printed.
1498 (defvar *last-format-string* nil)
1499 (defvar *last-format-args* nil)
1500 (declaim (type (or string null) *last-format-string*))
1501 (declaim (type list *last-format-args*))
1503 ;;; The number of times that the last error message has been emitted,
1504 ;;; so that we can compress duplicate error messages.
1505 (defvar *last-message-count* 0)
1506 (declaim (type index *last-message-count*))
1508 ;;; If the last message was given more than once, then print out an
1509 ;;; indication of how many times it was repeated. We reset the message count
1510 ;;; when we are done.
1511 (defun note-message-repeats (&optional (terpri t))
1512 (cond ((= *last-message-count* 1)
1513 (when terpri (terpri *error-output*)))
1514 ((> *last-message-count* 1)
1515 (format *error-output* "~&; [Last message occurs ~D times.]~2%"
1516 *last-message-count*)))
1517 (setq *last-message-count* 0))
1519 ;;; Print out the message, with appropriate context if we can find it.
1520 ;;; If the context is different from the context of the last message
1521 ;;; we printed, then we print the context. If the original source is
1522 ;;; different from the source we are working on, then we print the
1523 ;;; current source in addition to the original source.
1525 ;;; We suppress printing of messages identical to the previous, but
1526 ;;; record the number of times that the message is repeated.
1527 (defun print-compiler-message (format-string format-args)
1529 (declare (type simple-string format-string))
1530 (declare (type list format-args))
1532 (let ((stream *error-output*)
1533 (context (find-error-context format-args)))
1536 (let ((file (compiler-error-context-file-name context))
1537 (in (compiler-error-context-context context))
1538 (form (compiler-error-context-original-source context))
1539 (enclosing (compiler-error-context-enclosing-source context))
1540 (source (compiler-error-context-source context))
1541 (last *last-error-context*))
1544 (equal file (compiler-error-context-file-name last)))
1545 (when (pathnamep file)
1546 (note-message-repeats)
1548 (format stream "~2&; file: ~A~%" (namestring file))))
1551 (equal in (compiler-error-context-context last)))
1552 (note-message-repeats)
1554 (format stream "~&")
1555 (pprint-logical-block (stream nil :per-line-prefix "; ")
1556 (format stream "in:~{~<~% ~4:;~{ ~S~}~>~^ =>~}" in))
1557 (format stream "~%"))
1562 (compiler-error-context-original-source last)))
1563 (note-message-repeats)
1565 (format stream "~&")
1566 (pprint-logical-block (stream nil :per-line-prefix "; ")
1567 (format stream " ~A" form))
1568 (format stream "~&"))
1572 (compiler-error-context-enclosing-source last)))
1574 (note-message-repeats)
1576 (format stream "~&; --> ~{~<~%; --> ~1:;~A~> ~}~%" enclosing)))
1579 (equal source (compiler-error-context-source last)))
1580 (setq *last-format-string* nil)
1582 (note-message-repeats)
1583 (dolist (src source)
1584 (format stream "~&")
1585 (write-string "; ==>" stream)
1586 (format stream "~&")
1587 (pprint-logical-block (stream nil :per-line-prefix "; ")
1588 (write-string src stream)))))))
1590 (format stream "~&")
1591 (note-message-repeats)
1592 (setq *last-format-string* nil)
1593 (format stream "~&")))
1595 (setq *last-error-context* context)
1597 (unless (and (equal format-string *last-format-string*)
1598 (tree-equal format-args *last-format-args*))
1599 (note-message-repeats nil)
1600 (setq *last-format-string* format-string)
1601 (setq *last-format-args* format-args)
1602 (let ((*print-level* *compiler-error-print-level*)
1603 (*print-length* *compiler-error-print-length*)
1604 (*print-lines* *compiler-error-print-lines*))
1605 (format stream "~&")
1606 (pprint-logical-block (stream nil :per-line-prefix "; ")
1607 (format stream "~&~?" format-string format-args))
1608 (format stream "~&"))))
1610 (incf *last-message-count*)
1613 (defun print-compiler-condition (condition)
1614 (declare (type condition condition))
1615 (let (;; These different classes of conditions have different
1616 ;; effects on the return codes of COMPILE-FILE, so it's nice
1617 ;; for users to be able to pick them out by lexical search
1618 ;; through the output.
1619 (what (etypecase condition
1620 (style-warning 'style-warning)
1623 (multiple-value-bind (format-string format-args)
1624 (if (typep condition 'simple-condition)
1625 (values (simple-condition-format-control condition)
1626 (simple-condition-format-arguments condition))
1628 (list (with-output-to-string (s)
1629 (princ condition s)))))
1630 (print-compiler-message (format nil
1637 ;;; COMPILER-NOTE is vaguely like COMPILER-ERROR and the other
1638 ;;; condition-signalling functions, but it just writes some output instead of
1639 ;;; signalling. (In CMU CL, it did signal a condition, but this didn't seem to
1640 ;;; work all that well; it was weird to have COMPILE-FILE return with
1641 ;;; WARNINGS-P set when the only problem was that the compiler couldn't figure
1642 ;;; out how to compile something as efficiently as it liked.)
1643 (defun compiler-note (format-string &rest format-args)
1644 (unless (if *compiler-error-context*
1645 (policy *compiler-error-context* (= inhibit-warnings 3))
1646 (policy nil (= inhibit-warnings 3)))
1647 (incf *compiler-note-count*)
1648 (print-compiler-message (format nil "note: ~A" format-string)
1652 ;;; Issue a note when we might or might not be in the compiler.
1653 (defun maybe-compiler-note (&rest rest)
1654 (if (boundp '*lexenv*) ; if we're in the compiler
1655 (apply #'compiler-note rest)
1656 (let ((stream *error-output*))
1657 (pprint-logical-block (stream nil :per-line-prefix ";")
1659 (format stream " note: ~3I~_")
1660 (pprint-logical-block (stream nil)
1661 (apply #'format stream rest)))
1662 (fresh-line stream)))) ; (outside logical block, no per-line-prefix)
1664 ;;; The politically correct way to print out progress messages and
1665 ;;; such like. We clear the current error context so that we know that
1666 ;;; it needs to be reprinted, and we also Force-Output so that the
1667 ;;; message gets seen right away.
1668 (declaim (ftype (function (string &rest t) (values)) compiler-mumble))
1669 (defun compiler-mumble (format-string &rest format-args)
1670 (note-message-repeats)
1671 (setq *last-error-context* nil)
1672 (apply #'format *error-output* format-string format-args)
1673 (force-output *error-output*)
1676 ;;; Return a string that somehow names the code in Component. We use
1677 ;;; the source path for the bind node for an arbitrary entry point to
1678 ;;; find the source context, then return that as a string.
1679 (declaim (ftype (function (component) simple-string) find-component-name))
1680 (defun find-component-name (component)
1681 (let ((ep (first (block-succ (component-head component)))))
1682 (assert ep () "no entry points?")
1683 (multiple-value-bind (form context)
1684 (find-original-source
1685 (node-source-path (continuation-next (block-start ep))))
1686 (declare (ignore form))
1687 (let ((*print-level* 2)
1688 (*print-pretty* nil))
1689 (format nil "~{~{~S~^ ~}~^ => ~}" context)))))
1691 ;;;; condition system interface
1693 ;;; Keep track of how many times each kind of condition happens.
1694 (defvar *compiler-error-count*)
1695 (defvar *compiler-warning-count*)
1696 (defvar *compiler-style-warning-count*)
1697 (defvar *compiler-note-count*)
1699 ;;; Keep track of whether any surrounding COMPILE or COMPILE-FILE call
1700 ;;; should return WARNINGS-P or FAILURE-P.
1701 (defvar *failure-p*)
1702 (defvar *warnings-p*)
1704 ;;; condition handlers established by the compiler. We re-signal the
1705 ;;; condition, then if it isn't handled, we increment our warning
1706 ;;; counter and print the error message.
1707 (defun compiler-error-handler (condition)
1709 (incf *compiler-error-count*)
1710 (setf *warnings-p* t
1712 (print-compiler-condition condition)
1713 (continue condition))
1714 (defun compiler-warning-handler (condition)
1716 (incf *compiler-warning-count*)
1717 (setf *warnings-p* t
1719 (print-compiler-condition condition)
1720 (muffle-warning condition))
1721 (defun compiler-style-warning-handler (condition)
1723 (incf *compiler-style-warning-count*)
1724 (setf *warnings-p* t)
1725 (print-compiler-condition condition)
1726 (muffle-warning condition))
1728 ;;;; undefined warnings
1730 (defvar *undefined-warning-limit* 3
1732 "If non-null, then an upper limit on the number of unknown function or type
1733 warnings that the compiler will print for any given name in a single
1734 compilation. This prevents excessive amounts of output when the real
1735 problem is a missing definition (as opposed to a typo in the use.)")
1737 ;;; Make an entry in the *UNDEFINED-WARNINGS* describing a reference
1738 ;;; to NAME of the specified KIND. If we have exceeded the warning
1739 ;;; limit, then just increment the count, otherwise note the current
1742 ;;; Undefined types are noted by a condition handler in
1743 ;;; WITH-COMPILATION-UNIT, which can potentially be invoked outside
1744 ;;; the compiler, hence the BOUNDP check.
1745 (defun note-undefined-reference (name kind)
1747 ;; (POLICY NIL ..) isn't well-defined except in IR1
1748 ;; conversion. This BOUNDP test seems to be a test for
1749 ;; whether IR1 conversion is going on.
1751 ;; FIXME: I'm pretty sure the INHIBIT-WARNINGS test below
1752 ;; isn't a good idea; we should have INHIBIT-WARNINGS
1753 ;; affect compiler notes, not STYLE-WARNINGs. And I'm not
1754 ;; sure what the BOUNDP '*LEXENV* test above is for; it's
1755 ;; likely a good idea, but it probably deserves an
1756 ;; explanatory comment.
1757 (policy nil (= inhibit-warnings 3)))
1758 (let* ((found (dolist (warning *undefined-warnings* nil)
1759 (when (and (equal (undefined-warning-name warning) name)
1760 (eq (undefined-warning-kind warning) kind))
1763 (make-undefined-warning :name name :kind kind))))
1764 (unless found (push res *undefined-warnings*))
1765 (when (or (not *undefined-warning-limit*)
1766 (< (undefined-warning-count res) *undefined-warning-limit*))
1767 (push (find-error-context (list name))
1768 (undefined-warning-warnings res)))
1769 (incf (undefined-warning-count res))))
1774 ;;; Apply a function to some arguments, returning a list of the values
1775 ;;; resulting of the evaluation. If an error is signalled during the
1776 ;;; application, then we print a warning message and return NIL as our
1777 ;;; second value to indicate this. Node is used as the error context
1778 ;;; for any error message, and Context is a string that is spliced
1779 ;;; into the warning.
1780 (declaim (ftype (function ((or symbol function) list node string)
1781 (values list boolean))
1783 (defun careful-call (function args node context)
1785 (multiple-value-list
1786 (handler-case (apply function args)
1788 (let ((*compiler-error-context* node))
1789 (compiler-warning "Lisp error during ~A:~%~A" context condition)
1790 (return-from careful-call (values nil nil))))))
1793 ;;;; utilities used at run-time for parsing keyword args in IR1
1795 ;;; This function is used by the result of Parse-Deftransform to find
1796 ;;; the continuation for the value of the keyword argument Key in the
1797 ;;; list of continuations Args. It returns the continuation if the
1798 ;;; keyword is present, or NIL otherwise. The legality and
1799 ;;; constantness of the keywords should already have been checked.
1800 (declaim (ftype (function (list keyword) (or continuation null))
1801 find-keyword-continuation))
1802 (defun find-keyword-continuation (args key)
1803 (do ((arg args (cddr arg)))
1805 (when (eq (continuation-value (first arg)) key)
1806 (return (second arg)))))
1808 ;;; This function is used by the result of Parse-Deftransform to
1809 ;;; verify that alternating continuations in Args are constant and
1810 ;;; that there is an even number of args.
1811 (declaim (ftype (function (list) boolean) check-keywords-constant))
1812 (defun check-keywords-constant (args)
1813 (do ((arg args (cddr arg)))
1815 (unless (and (rest arg)
1816 (constant-continuation-p (first arg)))
1819 ;;; This function is used by the result of Parse-Deftransform to
1820 ;;; verify that the list of continuations Args is a well-formed
1821 ;;; keyword arglist and that only keywords present in the list Keys
1823 (declaim (ftype (function (list list) boolean) check-transform-keys))
1824 (defun check-transform-keys (args keys)
1825 (and (check-keywords-constant args)
1826 (do ((arg args (cddr arg)))
1828 (unless (member (continuation-value (first arg)) keys)
1833 ;;; Called by the expansion of the EVENT macro.
1834 (declaim (ftype (function (event-info (or node null)) *) %event))
1835 (defun %event (info node)
1836 (incf (event-info-count info))
1837 (when (and (>= (event-info-level info) *event-note-threshold*)
1839 (policy node (= inhibit-warnings 0))
1840 (policy nil (= inhibit-warnings 0))))
1841 (let ((*compiler-error-context* node))
1842 (compiler-note (event-info-description info))))
1844 (let ((action (event-info-action info)))
1845 (when action (funcall action node))))