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 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))
157 ;;; Replace all uses of OLD with uses of NEW, where NEW has an
158 ;;; arbitary number of uses. If NEW will end up with more than one
159 ;;; use, then we must arrange for it to start a block if it doesn't
161 (defun substitute-continuation-uses (new old)
162 (declare (type continuation old new))
163 (unless (and (eq (continuation-kind new) :unused)
164 (eq (continuation-kind old) :inside-block))
165 (ensure-block-start new))
168 (delete-continuation-use node)
169 (add-continuation-use node new))
170 (dolist (lexenv-use (continuation-lexenv-uses old))
171 (setf (cadr lexenv-use) new))
173 (reoptimize-continuation new)
176 ;;;; block starting/creation
178 ;;; Return the block that CONT is the start of, making a block if
179 ;;; necessary. This function is called by IR1 translators which may
180 ;;; cause a continuation to be used more than once. Every continuation
181 ;;; which may be used more than once must start a block by the time
182 ;;; that anyone does a USE-CONTINUATION on it.
184 ;;; We also throw the block into the next/prev list for the
185 ;;; *CURRENT-COMPONENT* so that we keep track of which blocks we have
187 (defun continuation-starts-block (cont)
188 (declare (type continuation cont))
189 (ecase (continuation-kind cont)
191 (aver (not (continuation-block cont)))
192 (let* ((head (component-head *current-component*))
193 (next (block-next head))
194 (new-block (make-block cont)))
195 (setf (block-next new-block) next)
196 (setf (block-prev new-block) head)
197 (setf (block-prev next) new-block)
198 (setf (block-next head) new-block)
199 (setf (continuation-block cont) new-block)
200 (setf (continuation-use cont) nil)
201 (setf (continuation-kind cont) :block-start)
204 (continuation-block cont))))
206 ;;; Ensure that Cont is the start of a block (or deleted) so that the use
207 ;;; set can be freely manipulated.
208 ;;; -- If the continuation is :Unused or is :Inside-Block and the Cont of Last
209 ;;; in its block, then we make it the start of a new deleted block.
210 ;;; -- If the continuation is :Inside-Block inside a block, then we split the
211 ;;; block using Node-Ends-Block, which makes the continuation be a
213 (defun ensure-block-start (cont)
214 (declare (type continuation cont))
215 (let ((kind (continuation-kind cont)))
217 ((:deleted :block-start :deleted-block-start))
218 ((:unused :inside-block)
219 (let ((block (continuation-block cont)))
220 (cond ((or (eq kind :unused)
221 (eq (node-cont (block-last block)) cont))
222 (setf (continuation-block cont)
223 (make-block-key :start cont
225 :start-uses (find-uses cont)))
226 (setf (continuation-kind cont) :deleted-block-start))
228 (node-ends-block (continuation-use cont))))))))
231 ;;;; miscellaneous shorthand functions
233 ;;; Return the home (i.e. enclosing non-LET) CLAMBDA for NODE. Since
234 ;;; the LEXENV-LAMBDA may be deleted, we must chain up the
235 ;;; LAMBDA-CALL-LEXENV thread until we find a CLAMBDA that isn't
236 ;;; deleted, and then return its home.
237 (declaim (maybe-inline node-home-lambda))
238 (defun node-home-lambda (node)
239 (declare (type node node))
240 (do ((fun (lexenv-lambda (node-lexenv node))
241 (lexenv-lambda (lambda-call-lexenv fun))))
242 ((not (eq (functional-kind fun) :deleted))
244 (when (eq (lambda-home fun) fun)
247 #!-sb-fluid (declaim (inline node-block node-tlf-number))
248 (declaim (maybe-inline node-physenv))
249 (defun node-block (node)
250 (declare (type node node))
251 (the cblock (continuation-block (node-prev node))))
252 (defun node-physenv (node)
253 (declare (type node node))
254 #!-sb-fluid (declare (inline node-home-lambda))
255 (the physenv (lambda-physenv (node-home-lambda node))))
257 ;;; Return the enclosing cleanup for environment of the first or last node
259 (defun block-start-cleanup (block)
260 (declare (type cblock block))
261 (node-enclosing-cleanup (continuation-next (block-start block))))
262 (defun block-end-cleanup (block)
263 (declare (type cblock block))
264 (node-enclosing-cleanup (block-last block)))
266 ;;; Return the non-LET LAMBDA that holds BLOCK's code.
267 (defun block-home-lambda (block)
268 (declare (type cblock block))
269 #!-sb-fluid (declare (inline node-home-lambda))
270 (node-home-lambda (block-last block)))
272 ;;; Return the IR1 physical environment for BLOCK.
273 (defun block-physenv (block)
274 (declare (type cblock block))
275 #!-sb-fluid (declare (inline node-home-lambda))
276 (lambda-physenv (node-home-lambda (block-last block))))
278 ;;; Return the Top Level Form number of PATH, i.e. the ordinal number
279 ;;; of its original source's top-level form in its compilation unit.
280 (defun source-path-tlf-number (path)
281 (declare (list path))
284 ;;; Return the (reversed) list for the PATH in the original source
285 ;;; (with the Top Level Form number last).
286 (defun source-path-original-source (path)
287 (declare (list path) (inline member))
288 (cddr (member 'original-source-start path :test #'eq)))
290 ;;; Return the Form Number of PATH's original source inside the Top
291 ;;; Level Form that contains it. This is determined by the order that
292 ;;; we walk the subforms of the top level source form.
293 (defun source-path-form-number (path)
294 (declare (list path) (inline member))
295 (cadr (member 'original-source-start path :test #'eq)))
297 ;;; Return a list of all the enclosing forms not in the original
298 ;;; source that converted to get to this form, with the immediate
299 ;;; source for node at the start of the list.
300 (defun source-path-forms (path)
301 (subseq path 0 (position 'original-source-start path)))
303 ;;; Return the innermost source form for NODE.
304 (defun node-source-form (node)
305 (declare (type node node))
306 (let* ((path (node-source-path node))
307 (forms (source-path-forms path)))
310 (values (find-original-source path)))))
312 ;;; Return NODE-SOURCE-FORM, T if continuation has a single use,
313 ;;; otherwise NIL, NIL.
314 (defun continuation-source (cont)
315 (let ((use (continuation-use cont)))
317 (values (node-source-form use) t)
320 ;;; Return a new LEXENV just like DEFAULT except for the specified
321 ;;; slot values. Values for the alist slots are NCONCed to the
322 ;;; beginning of the current value, rather than replacing it entirely.
323 (defun make-lexenv (&key (default *lexenv*)
324 functions variables blocks tags type-restrictions
326 (lambda (lexenv-lambda default))
327 (cleanup (lexenv-cleanup default))
328 (policy (lexenv-policy default)))
329 (macrolet ((frob (var slot)
330 `(let ((old (,slot default)))
334 (internal-make-lexenv
335 (frob functions lexenv-functions)
336 (frob variables lexenv-variables)
337 (frob blocks lexenv-blocks)
338 (frob tags lexenv-tags)
339 (frob type-restrictions lexenv-type-restrictions)
340 lambda cleanup policy
341 (frob options lexenv-options))))
343 ;;;; flow/DFO/component hackery
345 ;;; Join BLOCK1 and BLOCK2.
346 #!-sb-fluid (declaim (inline link-blocks))
347 (defun link-blocks (block1 block2)
348 (declare (type cblock block1 block2))
349 (setf (block-succ block1)
350 (if (block-succ block1)
351 (%link-blocks block1 block2)
353 (push block1 (block-pred block2))
355 (defun %link-blocks (block1 block2)
356 (declare (type cblock block1 block2) (inline member))
357 (let ((succ1 (block-succ block1)))
358 (aver (not (member block2 succ1 :test #'eq)))
359 (cons block2 succ1)))
361 ;;; This is like LINK-BLOCKS, but we separate BLOCK1 and BLOCK2. If
362 ;;; this leaves a successor with a single predecessor that ends in an
363 ;;; IF, then set BLOCK-TEST-MODIFIED so that any test constraint will
364 ;;; now be able to be propagated to the successor.
365 (defun unlink-blocks (block1 block2)
366 (declare (type cblock block1 block2))
367 (let ((succ1 (block-succ block1)))
368 (if (eq block2 (car succ1))
369 (setf (block-succ block1) (cdr succ1))
370 (do ((succ (cdr succ1) (cdr succ))
372 ((eq (car succ) block2)
373 (setf (cdr prev) (cdr succ)))
376 (let ((new-pred (delq block1 (block-pred block2))))
377 (setf (block-pred block2) new-pred)
378 (when (and new-pred (null (rest new-pred)))
379 (let ((pred-block (first new-pred)))
380 (when (if-p (block-last pred-block))
381 (setf (block-test-modified pred-block) t)))))
384 ;;; Swing the succ/pred link between BLOCK and OLD to be between BLOCK
385 ;;; and NEW. If BLOCK ends in an IF, then we have to fix up the
386 ;;; consequent/alternative blocks to point to NEW. We also set
387 ;;; BLOCK-TEST-MODIFIED so that any test constraint will be applied to
388 ;;; the new successor.
389 (defun change-block-successor (block old new)
390 (declare (type cblock new old block) (inline member))
391 (unlink-blocks block old)
392 (let ((last (block-last block))
393 (comp (block-component block)))
394 (setf (component-reanalyze comp) t)
397 (setf (block-test-modified block) t)
398 (let* ((succ-left (block-succ block))
399 (new (if (and (eq new (component-tail comp))
403 (unless (member new succ-left :test #'eq)
404 (link-blocks block new))
405 (macrolet ((frob (slot)
406 `(when (eq (,slot last) old)
407 (setf (,slot last) new))))
409 (frob if-alternative))))
411 (unless (member new (block-succ block) :test #'eq)
412 (link-blocks block new)))))
416 ;;; Unlink a block from the next/prev chain. We also null out the
418 (declaim (ftype (function (cblock) (values)) remove-from-dfo))
419 (defun remove-from-dfo (block)
420 (let ((next (block-next block))
421 (prev (block-prev block)))
422 (setf (block-component block) nil)
423 (setf (block-next prev) next)
424 (setf (block-prev next) prev))
427 ;;; Add BLOCK to the next/prev chain following AFTER. We also set the
428 ;;; Component to be the same as for AFTER.
429 (defun add-to-dfo (block after)
430 (declare (type cblock block after))
431 (let ((next (block-next after))
432 (comp (block-component after)))
433 (aver (not (eq (component-kind comp) :deleted)))
434 (setf (block-component block) comp)
435 (setf (block-next after) block)
436 (setf (block-prev block) after)
437 (setf (block-next block) next)
438 (setf (block-prev next) block))
441 ;;; Set the FLAG for all the blocks in COMPONENT to NIL, except for
442 ;;; the head and tail which are set to T.
443 (declaim (ftype (function (component) (values)) clear-flags))
444 (defun clear-flags (component)
445 (let ((head (component-head component))
446 (tail (component-tail component)))
447 (setf (block-flag head) t)
448 (setf (block-flag tail) t)
449 (do-blocks (block component)
450 (setf (block-flag block) nil)))
453 ;;; Make a component with no blocks in it. The BLOCK-FLAG is initially
454 ;;; true in the head and tail blocks.
455 (declaim (ftype (function nil component) make-empty-component))
456 (defun make-empty-component ()
457 (let* ((head (make-block-key :start nil :component nil))
458 (tail (make-block-key :start nil :component nil))
459 (res (make-component :head head :tail tail)))
460 (setf (block-flag head) t)
461 (setf (block-flag tail) t)
462 (setf (block-component head) res)
463 (setf (block-component tail) res)
464 (setf (block-next head) tail)
465 (setf (block-prev tail) head)
468 ;;; Make NODE the LAST node in its block, splitting the block if necessary.
469 ;;; The new block is added to the DFO immediately following NODE's block.
470 (defun node-ends-block (node)
471 (declare (type node node))
472 (let* ((block (node-block node))
473 (start (node-cont node))
474 (last (block-last block))
475 (last-cont (node-cont last)))
476 (unless (eq last node)
477 (aver (and (eq (continuation-kind start) :inside-block)
478 (not (block-delete-p block))))
479 (let* ((succ (block-succ block))
481 (make-block-key :start start
482 :component (block-component block)
483 :start-uses (list (continuation-use start))
484 :succ succ :last last)))
485 (setf (continuation-kind start) :block-start)
488 (cons new-block (remove block (block-pred b)))))
489 (setf (block-succ block) ())
490 (setf (block-last block) node)
491 (link-blocks block new-block)
492 (add-to-dfo new-block block)
493 (setf (component-reanalyze (block-component block)) t)
495 (do ((cont start (node-cont (continuation-next cont))))
497 (when (eq (continuation-kind last-cont) :inside-block)
498 (setf (continuation-block last-cont) new-block)))
499 (setf (continuation-block cont) new-block))
501 (setf (block-type-asserted block) t)
502 (setf (block-test-modified block) t))))
508 ;;; Deal with deleting the last (read) reference to a LAMBDA-VAR. We
509 ;;; iterate over all local calls flushing the corresponding argument,
510 ;;; allowing the computation of the argument to be deleted. We also
511 ;;; mark the let for reoptimization, since it may be that we have
512 ;;; deleted the last variable.
514 ;;; The LAMBDA-VAR may still have some SETs, but this doesn't cause
515 ;;; too much difficulty, since we can efficiently implement write-only
516 ;;; variables. We iterate over the sets, marking their blocks for dead
517 ;;; code flushing, since we can delete sets whose value is unused.
518 (defun delete-lambda-var (leaf)
519 (declare (type lambda-var leaf))
520 (let* ((fun (lambda-var-home leaf))
521 (n (position leaf (lambda-vars fun))))
522 (dolist (ref (leaf-refs fun))
523 (let* ((cont (node-cont ref))
524 (dest (continuation-dest cont)))
525 (when (and (combination-p dest)
526 (eq (basic-combination-fun dest) cont)
527 (eq (basic-combination-kind dest) :local))
528 (let* ((args (basic-combination-args dest))
530 (reoptimize-continuation arg)
532 (setf (elt args n) nil))))))
534 (dolist (set (lambda-var-sets leaf))
535 (setf (block-flush-p (node-block set)) t))
539 ;;; Note that something interesting has happened to VAR. We only deal
540 ;;; with LET variables, marking the corresponding initial value arg as
541 ;;; needing to be reoptimized.
542 (defun reoptimize-lambda-var (var)
543 (declare (type lambda-var var))
544 (let ((fun (lambda-var-home var)))
545 (when (and (eq (functional-kind fun) :let)
547 (do ((args (basic-combination-args
550 (first (leaf-refs fun)))))
552 (vars (lambda-vars fun) (cdr vars)))
554 (reoptimize-continuation (car args))))))
557 ;;; Delete a function that has no references. This need only be called
558 ;;; on functions that never had any references, since otherwise
559 ;;; DELETE-REF will handle the deletion.
560 (defun delete-functional (fun)
561 (aver (and (null (leaf-refs fun))
562 (not (functional-entry-function fun))))
564 (optional-dispatch (delete-optional-dispatch fun))
565 (clambda (delete-lambda fun)))
568 ;;; Deal with deleting the last reference to a LAMBDA. Since there is
569 ;;; only one way into a LAMBDA, deleting the last reference to a
570 ;;; LAMBDA ensures that there is no way to reach any of the code in
571 ;;; it. So we just set the FUNCTIONAL-KIND for FUN and its LETs to
572 ;;; :DELETED, causing IR1 optimization to delete blocks in that
575 ;;; If the function isn't a LET, we unlink the function head and tail
576 ;;; from the component head and tail to indicate that the code is
577 ;;; unreachable. We also delete the function from COMPONENT-LAMBDAS
578 ;;; (it won't be there before local call analysis, but no matter.) If
579 ;;; the lambda was never referenced, we give a note.
581 ;;; If the lambda is an XEP, then we null out the ENTRY-FUNCTION in its
582 ;;; ENTRY-FUNCTION so that people will know that it is not an entry point
584 (defun delete-lambda (leaf)
585 (declare (type clambda leaf))
586 (let ((kind (functional-kind leaf))
587 (bind (lambda-bind leaf)))
588 (aver (not (member kind '(:deleted :optional :top-level))))
589 (aver (not (functional-has-external-references-p leaf)))
590 (setf (functional-kind leaf) :deleted)
591 (setf (lambda-bind leaf) nil)
592 (dolist (let (lambda-lets leaf))
593 (setf (lambda-bind let) nil)
594 (setf (functional-kind let) :deleted))
596 (if (member kind '(:let :mv-let :assignment))
597 (let ((home (lambda-home leaf)))
598 (setf (lambda-lets home) (delete leaf (lambda-lets home))))
599 (let* ((bind-block (node-block bind))
600 (component (block-component bind-block))
601 (return (lambda-return leaf)))
602 (aver (null (leaf-refs leaf)))
603 (unless (leaf-ever-used leaf)
604 (let ((*compiler-error-context* bind))
605 (compiler-note "deleting unused function~:[.~;~:*~% ~S~]"
607 (unlink-blocks (component-head component) bind-block)
609 (unlink-blocks (node-block return) (component-tail component)))
610 (setf (component-reanalyze component) t)
611 (let ((tails (lambda-tail-set leaf)))
612 (setf (tail-set-functions tails)
613 (delete leaf (tail-set-functions tails)))
614 (setf (lambda-tail-set leaf) nil))
615 (setf (component-lambdas component)
616 (delete leaf (component-lambdas component)))))
618 (when (eq kind :external)
619 (let ((fun (functional-entry-function leaf)))
620 (setf (functional-entry-function fun) nil)
621 (when (optional-dispatch-p fun)
622 (delete-optional-dispatch fun)))))
626 ;;; Deal with deleting the last reference to an OPTIONAL-DISPATCH. We
627 ;;; have to be a bit more careful than with lambdas, since DELETE-REF
628 ;;; is used both before and after local call analysis. Afterward, all
629 ;;; references to still-existing OPTIONAL-DISPATCHes have been moved
630 ;;; to the XEP, leaving it with no references at all. So we look at
631 ;;; the XEP to see whether an optional-dispatch is still really being
632 ;;; used. But before local call analysis, there are no XEPs, and all
633 ;;; references are direct.
635 ;;; When we do delete the OPTIONAL-DISPATCH, we grovel all of its
636 ;;; entry-points, making them be normal lambdas, and then deleting the
637 ;;; ones with no references. This deletes any e-p lambdas that were
638 ;;; either never referenced, or couldn't be deleted when the last
639 ;;; deference was deleted (due to their :OPTIONAL kind.)
641 ;;; Note that the last optional ep may alias the main entry, so when
642 ;;; we process the main entry, its kind may have been changed to NIL
643 ;;; or even converted to a let.
644 (defun delete-optional-dispatch (leaf)
645 (declare (type optional-dispatch leaf))
646 (let ((entry (functional-entry-function leaf)))
647 (unless (and entry (leaf-refs entry))
648 (aver (or (not entry) (eq (functional-kind entry) :deleted)))
649 (setf (functional-kind leaf) :deleted)
652 (unless (eq (functional-kind fun) :deleted)
653 (aver (eq (functional-kind fun) :optional))
654 (setf (functional-kind fun) nil)
655 (let ((refs (leaf-refs fun)))
659 (or (maybe-let-convert fun)
660 (maybe-convert-to-assignment fun)))
662 (maybe-convert-to-assignment fun)))))))
664 (dolist (ep (optional-dispatch-entry-points leaf))
666 (when (optional-dispatch-more-entry leaf)
667 (frob (optional-dispatch-more-entry leaf)))
668 (let ((main (optional-dispatch-main-entry leaf)))
669 (when (eq (functional-kind main) :optional)
674 ;;; Do stuff to delete the semantic attachments of a REF node. When
675 ;;; this leaves zero or one reference, we do a type dispatch off of
676 ;;; the leaf to determine if a special action is appropriate.
677 (defun delete-ref (ref)
678 (declare (type ref ref))
679 (let* ((leaf (ref-leaf ref))
680 (refs (delete ref (leaf-refs leaf))))
681 (setf (leaf-refs leaf) refs)
685 (lambda-var (delete-lambda-var leaf))
687 (ecase (functional-kind leaf)
688 ((nil :let :mv-let :assignment :escape :cleanup)
689 (aver (not (functional-entry-function leaf)))
690 (delete-lambda leaf))
692 (delete-lambda leaf))
693 ((:deleted :optional))))
695 (unless (eq (functional-kind leaf) :deleted)
696 (delete-optional-dispatch leaf)))))
699 (clambda (or (maybe-let-convert leaf)
700 (maybe-convert-to-assignment leaf)))
701 (lambda-var (reoptimize-lambda-var leaf))))
704 (clambda (maybe-convert-to-assignment leaf))))))
708 ;;; This function is called by people who delete nodes; it provides a
709 ;;; way to indicate that the value of a continuation is no longer
710 ;;; used. We null out the CONTINUATION-DEST, set FLUSH-P in the blocks
711 ;;; containing uses of CONT and set COMPONENT-REOPTIMIZE. If the PREV
712 ;;; of the use is deleted, then we blow off reoptimization.
714 ;;; If the continuation is :Deleted, then we don't do anything, since
715 ;;; all semantics have already been flushed. :DELETED-BLOCK-START
716 ;;; start continuations are treated just like :BLOCK-START; it is
717 ;;; possible that the continuation may be given a new dest (e.g. by
718 ;;; SUBSTITUTE-CONTINUATION), so we don't want to delete it.
719 (defun flush-dest (cont)
720 (declare (type continuation cont))
722 (unless (eq (continuation-kind cont) :deleted)
723 (aver (continuation-dest cont))
724 (setf (continuation-dest cont) nil)
726 (let ((prev (node-prev use)))
727 (unless (eq (continuation-kind prev) :deleted)
728 (let ((block (continuation-block prev)))
729 (setf (component-reoptimize (block-component block)) t)
730 (setf (block-attributep (block-flags block) flush-p type-asserted)
733 (setf (continuation-%type-check cont) nil)
737 ;;; Do a graph walk backward from BLOCK, marking all predecessor
738 ;;; blocks with the DELETE-P flag.
739 (defun mark-for-deletion (block)
740 (declare (type cblock block))
741 (unless (block-delete-p block)
742 (setf (block-delete-p block) t)
743 (setf (component-reanalyze (block-component block)) t)
744 (dolist (pred (block-pred block))
745 (mark-for-deletion pred)))
748 ;;; Delete CONT, eliminating both control and value semantics. We set
749 ;;; FLUSH-P and COMPONENT-REOPTIMIZE similarly to in FLUSH-DEST. Here
750 ;;; we must get the component from the use block, since the
751 ;;; continuation may be a :DELETED-BLOCK-START.
753 ;;; If CONT has DEST, then it must be the case that the DEST is
754 ;;; unreachable, since we can't compute the value desired. In this
755 ;;; case, we call MARK-FOR-DELETION to cause the DEST block and its
756 ;;; predecessors to tell people to ignore them, and to cause them to
757 ;;; be deleted eventually.
758 (defun delete-continuation (cont)
759 (declare (type continuation cont))
760 (aver (not (eq (continuation-kind cont) :deleted)))
763 (let ((prev (node-prev use)))
764 (unless (eq (continuation-kind prev) :deleted)
765 (let ((block (continuation-block prev)))
766 (setf (block-attributep (block-flags block) flush-p type-asserted) t)
767 (setf (component-reoptimize (block-component block)) t)))))
769 (let ((dest (continuation-dest cont)))
771 (let ((prev (node-prev dest)))
773 (not (eq (continuation-kind prev) :deleted)))
774 (let ((block (continuation-block prev)))
775 (unless (block-delete-p block)
776 (mark-for-deletion block)))))))
778 (setf (continuation-kind cont) :deleted)
779 (setf (continuation-dest cont) nil)
780 (setf (continuation-next cont) nil)
781 (setf (continuation-asserted-type cont) *empty-type*)
782 (setf (continuation-%derived-type cont) *empty-type*)
783 (setf (continuation-use cont) nil)
784 (setf (continuation-block cont) nil)
785 (setf (continuation-reoptimize cont) nil)
786 (setf (continuation-%type-check cont) nil)
787 (setf (continuation-info cont) nil)
791 ;;; This function does what is necessary to eliminate the code in it
792 ;;; from the IR1 representation. This involves unlinking it from its
793 ;;; predecessors and successors and deleting various node-specific
794 ;;; semantic information.
796 ;;; We mark the START as has having no next and remove the last node
797 ;;; from its CONT's uses. We also flush the DEST for all continuations
798 ;;; whose values are received by nodes in the block.
799 (defun delete-block (block)
800 (declare (type cblock block))
801 (aver (block-component block)) ; else block is already deleted!
802 (note-block-deletion block)
803 (setf (block-delete-p block) t)
805 (let* ((last (block-last block))
806 (cont (node-cont last)))
807 (delete-continuation-use last)
808 (if (eq (continuation-kind cont) :unused)
809 (delete-continuation cont)
810 (reoptimize-continuation cont)))
812 (dolist (b (block-pred block))
813 (unlink-blocks b block))
814 (dolist (b (block-succ block))
815 (unlink-blocks block b))
817 (do-nodes (node cont block)
819 (ref (delete-ref node))
821 (flush-dest (if-test node)))
822 ;; The next two cases serve to maintain the invariant that a LET
823 ;; always has a well-formed COMBINATION, REF and BIND. We delete
824 ;; the lambda whenever we delete any of these, but we must be
825 ;; careful that this LET has not already been partially deleted.
827 (when (and (eq (basic-combination-kind node) :local)
828 ;; Guards COMBINATION-LAMBDA agains the REF being deleted.
829 (continuation-use (basic-combination-fun node)))
830 (let ((fun (combination-lambda node)))
831 ;; If our REF was the 2'nd to last ref, and has been deleted, then
832 ;; Fun may be a LET for some other combination.
833 (when (and (member (functional-kind fun) '(:let :mv-let))
834 (eq (let-combination fun) node))
835 (delete-lambda fun))))
836 (flush-dest (basic-combination-fun node))
837 (dolist (arg (basic-combination-args node))
838 (when arg (flush-dest arg))))
840 (let ((lambda (bind-lambda node)))
841 (unless (eq (functional-kind lambda) :deleted)
842 (aver (member (functional-kind lambda) '(:let :mv-let :assignment)))
843 (delete-lambda lambda))))
845 (let ((value (exit-value node))
846 (entry (exit-entry node)))
850 (setf (entry-exits entry)
851 (delete node (entry-exits entry))))))
853 (flush-dest (return-result node))
854 (delete-return node))
856 (flush-dest (set-value node))
857 (let ((var (set-var node)))
858 (setf (basic-var-sets var)
859 (delete node (basic-var-sets var))))))
861 (delete-continuation (node-prev node)))
863 (remove-from-dfo block)
866 ;;; Do stuff to indicate that the return node Node is being deleted.
867 ;;; We set the RETURN to NIL.
868 (defun delete-return (node)
869 (declare (type creturn node))
870 (let ((fun (return-lambda node)))
871 (aver (lambda-return fun))
872 (setf (lambda-return fun) nil))
875 ;;; If any of the VARS in FUN was never referenced and was not
876 ;;; declared IGNORE, then complain.
877 (defun note-unreferenced-vars (fun)
878 (declare (type clambda fun))
879 (dolist (var (lambda-vars fun))
880 (unless (or (leaf-ever-used var)
881 (lambda-var-ignorep var))
882 (let ((*compiler-error-context* (lambda-bind fun)))
883 (unless (policy *compiler-error-context* (= inhibit-warnings 3))
884 ;; ANSI section "3.2.5 Exceptional Situations in the Compiler"
885 ;; requires this to be a STYLE-WARNING.
886 (compiler-style-warning "The variable ~S is defined but never used."
888 (setf (leaf-ever-used var) t))))
891 (defvar *deletion-ignored-objects* '(t nil))
893 ;;; Return true if we can find OBJ in FORM, NIL otherwise. We bound
894 ;;; our recursion so that we don't get lost in circular structures. We
895 ;;; ignore the car of forms if they are a symbol (to prevent confusing
896 ;;; function referencess with variables), and we also ignore anything
898 (defun present-in-form (obj form depth)
899 (declare (type (integer 0 20) depth))
900 (cond ((= depth 20) nil)
904 (let ((first (car form))
906 (if (member first '(quote function))
908 (or (and (not (symbolp first))
909 (present-in-form obj first depth))
910 (do ((l (cdr form) (cdr l))
912 ((or (atom l) (> n 100))
915 (when (present-in-form obj (car l) depth)
918 ;;; This function is called on a block immediately before we delete
919 ;;; it. We check to see whether any of the code about to die appeared
920 ;;; in the original source, and emit a note if so.
922 ;;; If the block was in a lambda is now deleted, then we ignore the
923 ;;; whole block, since this case is picked off in DELETE-LAMBDA. We
924 ;;; also ignore the deletion of CRETURN nodes, since it is somewhat
925 ;;; reasonable for a function to not return, and there is a different
926 ;;; note for that case anyway.
928 ;;; If the actual source is an atom, then we use a bunch of heuristics
929 ;;; to guess whether this reference really appeared in the original
931 ;;; -- If a symbol, it must be interned and not a keyword.
932 ;;; -- It must not be an easily introduced constant (T or NIL, a fixnum
934 ;;; -- The atom must be "present" in the original source form, and
935 ;;; present in all intervening actual source forms.
936 (defun note-block-deletion (block)
937 (let ((home (block-home-lambda block)))
938 (unless (eq (functional-kind home) :deleted)
939 (do-nodes (node cont block)
940 (let* ((path (node-source-path node))
941 (first (first path)))
942 (when (or (eq first 'original-source-start)
944 (or (not (symbolp first))
945 (let ((pkg (symbol-package first)))
947 (not (eq pkg (symbol-package :end))))))
948 (not (member first *deletion-ignored-objects*))
949 (not (typep first '(or fixnum character)))
951 (present-in-form first x 0))
952 (source-path-forms path))
953 (present-in-form first (find-original-source path)
955 (unless (return-p node)
956 (let ((*compiler-error-context* node))
957 (compiler-note "deleting unreachable code")))
961 ;;; Delete a node from a block, deleting the block if there are no
962 ;;; nodes left. We remove the node from the uses of its CONT, but we
963 ;;; don't deal with cleaning up any type-specific semantic
964 ;;; attachments. If the CONT is :UNUSED after deleting this use, then
965 ;;; we delete CONT. (Note :UNUSED is not the same as no uses. A
966 ;;; continuation will only become :UNUSED if it was :INSIDE-BLOCK
969 ;;; If the node is the last node, there must be exactly one successor.
970 ;;; We link all of our precedessors to the successor and unlink the
971 ;;; block. In this case, we return T, otherwise NIL. If no nodes are
972 ;;; left, and the block is a successor of itself, then we replace the
973 ;;; only node with a degenerate exit node. This provides a way to
974 ;;; represent the bodyless infinite loop, given the prohibition on
975 ;;; empty blocks in IR1.
976 (defun unlink-node (node)
977 (declare (type node node))
978 (let* ((cont (node-cont node))
979 (next (continuation-next cont))
980 (prev (node-prev node))
981 (block (continuation-block prev))
982 (prev-kind (continuation-kind prev))
983 (last (block-last block)))
985 (unless (eq (continuation-kind cont) :deleted)
986 (delete-continuation-use node)
987 (when (eq (continuation-kind cont) :unused)
988 (aver (not (continuation-dest cont)))
989 (delete-continuation cont)))
991 (setf (block-type-asserted block) t)
992 (setf (block-test-modified block) t)
994 (cond ((or (eq prev-kind :inside-block)
995 (and (eq prev-kind :block-start)
996 (not (eq node last))))
997 (cond ((eq node last)
998 (setf (block-last block) (continuation-use prev))
999 (setf (continuation-next prev) nil))
1001 (setf (continuation-next prev) next)
1002 (setf (node-prev next) prev)))
1003 (setf (node-prev node) nil)
1006 (aver (eq prev-kind :block-start))
1007 (aver (eq node last))
1008 (let* ((succ (block-succ block))
1009 (next (first succ)))
1010 (aver (and succ (null (cdr succ))))
1012 ((member block succ)
1013 (with-ir1-environment node
1014 (let ((exit (make-exit))
1015 (dummy (make-continuation)))
1016 (setf (continuation-next prev) nil)
1017 (prev-link exit prev)
1018 (add-continuation-use exit dummy)
1019 (setf (block-last block) exit)))
1020 (setf (node-prev node) nil)
1023 (aver (eq (block-start-cleanup block)
1024 (block-end-cleanup block)))
1025 (unlink-blocks block next)
1026 (dolist (pred (block-pred block))
1027 (change-block-successor pred block next))
1028 (remove-from-dfo block)
1029 (cond ((continuation-dest prev)
1030 (setf (continuation-next prev) nil)
1031 (setf (continuation-kind prev) :deleted-block-start))
1033 (delete-continuation prev)))
1034 (setf (node-prev node) nil)
1037 ;;; Return true if NODE has been deleted, false if it is still a valid
1039 (defun node-deleted (node)
1040 (declare (type node node))
1041 (let ((prev (node-prev node)))
1043 (not (eq (continuation-kind prev) :deleted))
1044 (let ((block (continuation-block prev)))
1045 (and (block-component block)
1046 (not (block-delete-p block))))))))
1048 ;;; Delete all the blocks and functions in COMPONENT. We scan first
1049 ;;; marking the blocks as delete-p to prevent weird stuff from being
1050 ;;; triggered by deletion.
1051 (defun delete-component (component)
1052 (declare (type component component))
1053 (aver (null (component-new-functions component)))
1054 (setf (component-kind component) :deleted)
1055 (do-blocks (block component)
1056 (setf (block-delete-p block) t))
1057 (dolist (fun (component-lambdas component))
1058 (setf (functional-kind fun) nil)
1059 (setf (functional-entry-function fun) nil)
1060 (setf (leaf-refs fun) nil)
1061 (delete-functional fun))
1062 (do-blocks (block component)
1063 (delete-block block))
1066 ;;; Convert code of the form
1067 ;;; (FOO ... (FUN ...) ...)
1069 ;;; (FOO ... ... ...).
1070 ;;; In other words, replace the function combination FUN by its
1071 ;;; arguments. If there are any problems with doing this, use GIVE-UP
1072 ;;; to blow out of whatever transform called this. Note, as the number
1073 ;;; of arguments changes, the transform must be prepared to return a
1074 ;;; lambda with a new lambda-list with the correct number of
1076 (defun extract-function-args (cont fun num-args)
1078 "If CONT is a call to FUN with NUM-ARGS args, change those arguments
1079 to feed directly to the continuation-dest of CONT, which must be
1081 (declare (type continuation cont)
1083 (type index num-args))
1084 (let ((outside (continuation-dest cont))
1085 (inside (continuation-use cont)))
1086 (aver (combination-p outside))
1087 (unless (combination-p inside)
1088 (give-up-ir1-transform))
1089 (let ((inside-fun (combination-fun inside)))
1090 (unless (eq (continuation-fun-name inside-fun) fun)
1091 (give-up-ir1-transform))
1092 (let ((inside-args (combination-args inside)))
1093 (unless (= (length inside-args) num-args)
1094 (give-up-ir1-transform))
1095 (let* ((outside-args (combination-args outside))
1096 (arg-position (position cont outside-args))
1097 (before-args (subseq outside-args 0 arg-position))
1098 (after-args (subseq outside-args (1+ arg-position))))
1099 (dolist (arg inside-args)
1100 (setf (continuation-dest arg) outside))
1101 (setf (combination-args inside) nil)
1102 (setf (combination-args outside)
1103 (append before-args inside-args after-args))
1104 (change-ref-leaf (continuation-use inside-fun)
1105 (find-free-function 'list "???"))
1106 (setf (combination-kind inside) :full)
1107 (setf (node-derived-type inside) *wild-type*)
1109 (setf (continuation-asserted-type cont) *wild-type*)
1114 ;;; Change the Leaf that a Ref refers to.
1115 (defun change-ref-leaf (ref leaf)
1116 (declare (type ref ref) (type leaf leaf))
1117 (unless (eq (ref-leaf ref) leaf)
1118 (push ref (leaf-refs leaf))
1120 (setf (ref-leaf ref) leaf)
1121 (let ((ltype (leaf-type leaf)))
1122 (if (fun-type-p ltype)
1123 (setf (node-derived-type ref) ltype)
1124 (derive-node-type ref ltype)))
1125 (reoptimize-continuation (node-cont ref)))
1128 ;;; Change all REFS for OLD-LEAF to NEW-LEAF.
1129 (defun substitute-leaf (new-leaf old-leaf)
1130 (declare (type leaf new-leaf old-leaf))
1131 (dolist (ref (leaf-refs old-leaf))
1132 (change-ref-leaf ref new-leaf))
1135 ;;; Like SUBSITUTE-LEAF, only there is a predicate on the Ref to tell
1136 ;;; whether to substitute.
1137 (defun substitute-leaf-if (test new-leaf old-leaf)
1138 (declare (type leaf new-leaf old-leaf) (type function test))
1139 (dolist (ref (leaf-refs old-leaf))
1140 (when (funcall test ref)
1141 (change-ref-leaf ref new-leaf)))
1144 ;;; Return a LEAF which represents the specified constant object. If
1145 ;;; the object is not in *CONSTANTS*, then we create a new constant
1146 ;;; LEAF and enter it.
1147 #!-sb-fluid (declaim (maybe-inline find-constant))
1148 (defun find-constant (object)
1149 (if (typep object '(or symbol number character instance))
1150 (or (gethash object *constants*)
1151 (setf (gethash object *constants*)
1152 (make-constant :value object
1154 :type (ctype-of object)
1155 :where-from :defined)))
1156 (make-constant :value object
1158 :type (ctype-of object)
1159 :where-from :defined)))
1161 ;;; If there is a non-local exit noted in ENTRY's environment that
1162 ;;; exits to CONT in that entry, then return it, otherwise return NIL.
1163 (defun find-nlx-info (entry cont)
1164 (declare (type entry entry) (type continuation cont))
1165 (let ((entry-cleanup (entry-cleanup entry)))
1166 (dolist (nlx (physenv-nlx-info (node-physenv entry)) nil)
1167 (when (and (eq (nlx-info-continuation nlx) cont)
1168 (eq (nlx-info-cleanup nlx) entry-cleanup))
1171 ;;;; functional hackery
1173 (declaim (ftype (function (functional) clambda) main-entry))
1174 (defun main-entry (functional)
1175 (etypecase functional
1176 (clambda functional)
1178 (optional-dispatch-main-entry functional))))
1180 ;;; RETURN true if FUNCTIONAL is a thing that can be treated like
1181 ;;; MV-BIND when it appears in an MV-CALL. All fixed arguments must be
1182 ;;; optional with null default and no SUPPLIED-P. There must be a
1183 ;;; &REST arg with no references.
1184 (declaim (ftype (function (functional) boolean) looks-like-an-mv-bind))
1185 (defun looks-like-an-mv-bind (functional)
1186 (and (optional-dispatch-p functional)
1187 (do ((arg (optional-dispatch-arglist functional) (cdr arg)))
1189 (let ((info (lambda-var-arg-info (car arg))))
1190 (unless info (return nil))
1191 (case (arg-info-kind info)
1193 (when (or (arg-info-supplied-p info) (arg-info-default info))
1196 (return (and (null (cdr arg)) (null (leaf-refs (car arg))))))
1200 ;;; Return true if function is an XEP. This is true of normal XEPs
1201 ;;; (:EXTERNAL kind) and top-level lambdas (:TOP-LEVEL kind.)
1202 (defun external-entry-point-p (fun)
1203 (declare (type functional fun))
1204 (not (null (member (functional-kind fun) '(:external :top-level)))))
1206 ;;; If CONT's only use is a non-notinline global function reference,
1207 ;;; then return the referenced symbol, otherwise NIL. If NOTINLINE-OK
1208 ;;; is true, then we don't care if the leaf is NOTINLINE.
1209 (defun continuation-fun-name (cont &optional notinline-ok)
1210 (declare (type continuation cont))
1211 (let ((use (continuation-use cont)))
1213 (let ((leaf (ref-leaf use)))
1214 (if (and (global-var-p leaf)
1215 (eq (global-var-kind leaf) :global-function)
1216 (or (not (defined-fun-p leaf))
1217 (not (eq (defined-fun-inlinep leaf) :notinline))
1223 ;;; Return the COMBINATION node that is the call to the LET FUN.
1224 (defun let-combination (fun)
1225 (declare (type clambda fun))
1226 (aver (member (functional-kind fun) '(:let :mv-let)))
1227 (continuation-dest (node-cont (first (leaf-refs fun)))))
1229 ;;; Return the initial value continuation for a LET variable, or NIL
1230 ;;; if there is none.
1231 (defun let-var-initial-value (var)
1232 (declare (type lambda-var var))
1233 (let ((fun (lambda-var-home var)))
1234 (elt (combination-args (let-combination fun))
1235 (position-or-lose var (lambda-vars fun)))))
1237 ;;; Return the LAMBDA that is called by the local Call.
1238 #!-sb-fluid (declaim (inline combination-lambda))
1239 (defun combination-lambda (call)
1240 (declare (type basic-combination call))
1241 (aver (eq (basic-combination-kind call) :local))
1242 (ref-leaf (continuation-use (basic-combination-fun call))))
1244 (defvar *inline-expansion-limit* 200
1246 "an upper limit on the number of inline function calls that will be expanded
1247 in any given code object (single function or block compilation)")
1249 ;;; Check whether NODE's component has exceeded its inline expansion
1250 ;;; limit, and warn if so, returning NIL.
1251 (defun inline-expansion-ok (node)
1252 (let ((expanded (incf (component-inline-expansions
1254 (node-block node))))))
1255 (cond ((> expanded *inline-expansion-limit*) nil)
1256 ((= expanded *inline-expansion-limit*)
1257 ;; FIXME: If the objective is to stop the recursive
1258 ;; expansion of inline functions, wouldn't it be more
1259 ;; correct to look back through surrounding expansions
1260 ;; (which are, I think, stored in the *CURRENT-PATH*, and
1261 ;; possibly stored elsewhere too) and suppress expansion
1262 ;; and print this warning when the function being proposed
1263 ;; for inline expansion is found there? (I don't like the
1264 ;; arbitrary numerical limit in principle, and I think
1265 ;; it'll be a nuisance in practice if we ever want the
1266 ;; compiler to be able to use WITH-COMPILATION-UNIT on
1267 ;; arbitrarily huge blocks of code. -- WHN)
1268 (let ((*compiler-error-context* node))
1269 (compiler-note "*INLINE-EXPANSION-LIMIT* (~D) was exceeded, ~
1270 probably trying to~% ~
1271 inline a recursive function."
1272 *inline-expansion-limit*))
1278 ;;; Apply a function to some arguments, returning a list of the values
1279 ;;; resulting of the evaluation. If an error is signalled during the
1280 ;;; application, then we print a warning message and return NIL as our
1281 ;;; second value to indicate this. Node is used as the error context
1282 ;;; for any error message, and Context is a string that is spliced
1283 ;;; into the warning.
1284 (declaim (ftype (function ((or symbol function) list node string)
1285 (values list boolean))
1287 (defun careful-call (function args node context)
1289 (multiple-value-list
1290 (handler-case (apply function args)
1292 (let ((*compiler-error-context* node))
1293 (compiler-warning "Lisp error during ~A:~%~A" context condition)
1294 (return-from careful-call (values nil nil))))))
1297 ;;;; utilities used at run-time for parsing &KEY args in IR1
1299 ;;; This function is used by the result of PARSE-DEFTRANSFORM to find
1300 ;;; the continuation for the value of the &KEY argument KEY in the
1301 ;;; list of continuations ARGS. It returns the continuation if the
1302 ;;; keyword is present, or NIL otherwise. The legality and
1303 ;;; constantness of the keywords should already have been checked.
1304 (declaim (ftype (function (list keyword) (or continuation null))
1305 find-keyword-continuation))
1306 (defun find-keyword-continuation (args key)
1307 (do ((arg args (cddr arg)))
1309 (when (eq (continuation-value (first arg)) key)
1310 (return (second arg)))))
1312 ;;; This function is used by the result of PARSE-DEFTRANSFORM to
1313 ;;; verify that alternating continuations in ARGS are constant and
1314 ;;; that there is an even number of args.
1315 (declaim (ftype (function (list) boolean) check-key-args-constant))
1316 (defun check-key-args-constant (args)
1317 (do ((arg args (cddr arg)))
1319 (unless (and (rest arg)
1320 (constant-continuation-p (first arg)))
1323 ;;; This function is used by the result of PARSE-DEFTRANSFORM to
1324 ;;; verify that the list of continuations ARGS is a well-formed &KEY
1325 ;;; arglist and that only keywords present in the list KEYS are
1327 (declaim (ftype (function (list list) boolean) check-transform-keys))
1328 (defun check-transform-keys (args keys)
1329 (and (check-key-args-constant args)
1330 (do ((arg args (cddr arg)))
1332 (unless (member (continuation-value (first arg)) keys)
1337 ;;; Called by the expansion of the EVENT macro.
1338 (declaim (ftype (function (event-info (or node null)) *) %event))
1339 (defun %event (info node)
1340 (incf (event-info-count info))
1341 (when (and (>= (event-info-level info) *event-note-threshold*)
1342 (policy (or node *lexenv*)
1343 (= inhibit-warnings 0)))
1344 (let ((*compiler-error-context* node))
1345 (compiler-note (event-info-description info))))
1347 (let ((action (event-info-action info)))
1348 (when action (funcall action node))))