1 ;;;; This file contains utilities for debugging the compiler --
2 ;;;; currently only stuff for checking the consistency of the IR1.
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 "This variable is bound to the format arguments when an error is signalled
20 (defvar *ignored-errors* (make-hash-table :test 'equal))
22 ;;; A definite inconsistency has been detected. Signal an error with
23 ;;; *args* bound to the list of the format args.
24 (declaim (ftype (function (string &rest t) (values)) barf))
25 (defun barf (string &rest *args*)
26 (unless (gethash string *ignored-errors*)
28 (apply #'error string *args*)
30 :report "Ignore this error.")
32 :report "Ignore this and all future occurrences of this error."
33 (setf (gethash string *ignored-errors*) t))))
36 (defvar *burp-action* :warn
38 "Action taken by the BURP function when a possible compiler bug is detected.
39 One of :WARN, :ERROR or :NONE.")
40 (declaim (type (member :warn :error :none) *burp-action*))
42 ;;; Called when something funny but possibly correct is noticed.
43 ;;; Otherwise similar to BARF.
44 (declaim (ftype (function (string &rest t) (values)) burp))
45 (defun burp (string &rest *args*)
47 (:warn (apply #'warn string *args*))
48 (:error (apply #'cerror "press on anyway." string *args*))
52 ;;; *SEEN-BLOCKS* is a hashtable with true values for all blocks which
53 ;;; appear in the DFO for one of the specified components.
55 ;;; *SEEN-FUNS* is similar, but records all the lambdas we
56 ;;; reached by recursing on top level functions.
57 ;;; FIXME: Is it really only LAMBDAs, not e.g. FUNCTIONALs? Then
58 ;;; shouldn't it be *SEEN-LAMBDAS*?
59 (defvar *seen-blocks* (make-hash-table :test 'eq))
60 (defvar *seen-funs* (make-hash-table :test 'eq))
62 ;;; Barf if NODE is in a block which wasn't reached during the graph
64 (declaim (ftype (function (node) (values)) check-node-reached))
65 (defun check-node-reached (node)
66 (unless (gethash (ctran-block (node-prev node)) *seen-blocks*)
67 (barf "~S was not reached." node))
70 ;;; Check everything that we can think of for consistency. When a
71 ;;; definite inconsistency is detected, we BARF. Possible problems
72 ;;; just cause us to BURP. Our argument is a list of components, but
73 ;;; we also look at the *FREE-VARS*, *FREE-FUNS* and *CONSTANTS*.
75 ;;; First we do a pre-pass which finds all the CBLOCKs and CLAMBDAs,
76 ;;; testing that they are linked together properly and entering them
77 ;;; in hashtables. Next, we iterate over the blocks again, looking at
78 ;;; the actual code and control flow. Finally, we scan the global leaf
79 ;;; hashtables, looking for lossage.
80 (declaim (ftype (function (list) (values)) check-ir1-consistency))
81 (defun check-ir1-consistency (components)
82 (clrhash *seen-blocks*)
84 (dolist (c components)
85 (let* ((head (component-head c))
86 (tail (component-tail c)))
87 (unless (and (null (block-pred head))
88 (null (block-succ tail)))
89 (barf "~S is malformed." c))
92 (block head (block-next block)))
94 (unless (eq prev tail)
95 (barf "wrong TAIL for DFO, ~S in ~S" prev c)))
96 (setf (gethash block *seen-blocks*) t)
97 (unless (eq (block-prev block) prev)
98 (barf "bad PREV for ~S, should be ~S" block prev))
99 (unless (or (eq block tail)
100 (eq (block-component block) c))
101 (barf "~S is not in ~S." block c)))
103 (when (or (loop-blocks c) (loop-inferiors c))
104 (do-blocks (block c :both)
105 (setf (block-flag block) nil))
106 (check-loop-consistency c nil)
107 (do-blocks (block c :both)
108 (unless (block-flag block)
109 (barf "~S was not in any loop." block))))
113 (check-fun-consistency components)
115 (dolist (c components)
116 (do ((block (block-next (component-head c)) (block-next block)))
117 ((null (block-next block)))
118 (check-block-consistency block)))
120 (maphash (lambda (k v)
122 (unless (or (constant-p v)
123 (and (global-var-p v)
124 (member (global-var-kind v)
125 '(:global :special :unknown))))
126 (barf "strange *FREE-VARS* entry: ~S" v))
127 (dolist (n (leaf-refs v))
128 (check-node-reached n))
129 (when (basic-var-p v)
130 (dolist (n (basic-var-sets v))
131 (check-node-reached n))))
134 (maphash (lambda (k v)
136 (unless (constant-p v)
137 (barf "strange *CONSTANTS* entry: ~S" v))
138 (dolist (n (leaf-refs v))
139 (check-node-reached n)))
142 (maphash (lambda (k v)
144 (unless (or (functional-p v)
145 (and (global-var-p v)
146 (eq (global-var-kind v) :global-function)))
147 (barf "strange *FREE-FUNS* entry: ~S" v))
148 (dolist (n (leaf-refs v))
149 (check-node-reached n)))
151 (clrhash *seen-funs*)
152 (clrhash *seen-blocks*)
155 ;;;; function consistency checking
157 (defun observe-functional (x)
158 (declare (type functional x))
159 (when (gethash x *seen-funs*)
160 (barf "~S was seen more than once." x))
161 (unless (eq (functional-kind x) :deleted)
162 (setf (gethash x *seen-funs*) t)))
164 ;;; Check that the specified function has been seen.
165 (defun check-fun-reached (fun where)
166 (declare (type functional fun))
167 (unless (gethash fun *seen-funs*)
168 (barf "unseen function ~S in ~S" fun where)))
170 ;;; In a CLAMBDA, check that the associated nodes are in seen blocks.
171 ;;; In an OPTIONAL-DISPATCH, check that the entry points were seen. If
172 ;;; the function is deleted, ignore it.
173 (defun check-fun-stuff (functional)
174 (ecase (functional-kind functional)
176 (let ((fun (functional-entry-fun functional)))
177 (check-fun-reached fun functional)
178 (when (functional-kind fun)
179 (barf "The function for XEP ~S has kind." functional))
180 (unless (eq (functional-entry-fun fun) functional)
181 (barf "bad back-pointer in function for XEP ~S" functional))))
182 ((:let :mv-let :assignment) ; i.e. SOMEWHAT-LETLIKE-P
183 (check-fun-reached (lambda-home functional) functional)
184 (when (functional-entry-fun functional)
185 (barf "The LET ~S has entry function." functional))
186 (unless (member functional (lambda-lets (lambda-home functional)))
187 (barf "The LET ~S is not in LETs for HOME." functional))
188 (unless (eq (functional-kind functional) :assignment)
189 (when (rest (leaf-refs functional))
190 (barf "The LET ~S has multiple references." functional)))
191 (when (lambda-lets functional)
192 (barf "LETs in a LET: ~S" functional)))
194 (when (functional-entry-fun functional)
195 (barf ":OPTIONAL ~S has an ENTRY-FUN." functional))
196 (let ((ef (lambda-optional-dispatch functional)))
197 (check-fun-reached ef functional)
198 (unless (or (member functional (optional-dispatch-entry-points ef)
200 (when (promise-ready-p ep)
202 (eq functional (optional-dispatch-more-entry ef))
203 (eq functional (optional-dispatch-main-entry ef)))
204 (barf ":OPTIONAL ~S is not an e-p for its OPTIONAL-DISPATCH ~S."
207 (unless (eq (functional-entry-fun functional) functional)
208 (barf "The ENTRY-FUN in ~S isn't a self-pointer." functional)))
209 ((nil :escape :cleanup)
210 (let ((ef (functional-entry-fun functional)))
212 (check-fun-reached ef functional)
213 (unless (eq (functional-kind ef) :external)
214 (barf "The ENTRY-FUN in ~S isn't an XEP: ~S." functional ef)))))
216 (return-from check-fun-stuff)))
218 (case (functional-kind functional)
219 ((nil :optional :external :toplevel :escape :cleanup)
220 (when (lambda-p functional)
221 (dolist (fun (lambda-lets functional))
222 (unless (eq (lambda-home fun) functional)
223 (barf "The home in ~S is not ~S." fun functional))
224 (check-fun-reached fun functional))
225 (unless (eq (lambda-home functional) functional)
226 (barf "home not self-pointer in ~S" functional)))))
228 (etypecase functional
230 (when (lambda-bind functional)
231 (check-node-reached (lambda-bind functional)))
232 (when (lambda-return functional)
233 (check-node-reached (lambda-return functional)))
235 (dolist (var (lambda-vars functional))
236 (dolist (ref (leaf-refs var))
237 (check-node-reached ref))
238 (dolist (set (basic-var-sets var))
239 (check-node-reached set))
240 (unless (eq (lambda-var-home var) functional)
241 (barf "HOME in ~S should be ~S." var functional))))
243 (dolist (ep (optional-dispatch-entry-points functional))
244 (when (promise-ready-p ep)
245 (check-fun-reached (force ep) functional)))
246 (let ((more (optional-dispatch-more-entry functional)))
247 (when more (check-fun-reached more functional)))
248 (check-fun-reached (optional-dispatch-main-entry functional)
251 (defun check-fun-consistency (components)
252 (dolist (c components)
253 (dolist (new-fun (component-new-functionals c))
254 (observe-functional new-fun))
255 (dolist (fun (component-lambdas c))
256 (when (eq (functional-kind fun) :external)
257 (let ((ef (functional-entry-fun fun)))
258 (when (optional-dispatch-p ef)
259 (observe-functional ef))))
260 (observe-functional fun)
261 (dolist (let (lambda-lets fun))
262 (observe-functional let))))
264 (dolist (c components)
265 (dolist (new-fun (component-new-functionals c))
266 (check-fun-stuff new-fun))
267 (dolist (fun (component-lambdas c))
268 (when (eq (functional-kind fun) :deleted)
269 (barf "deleted lambda ~S in Lambdas for ~S" fun c))
270 (check-fun-stuff fun)
271 (dolist (let (lambda-lets fun))
272 (check-fun-stuff let)))))
274 ;;;; loop consistency checking
277 ;;; Descend through the loop nesting and check that the tree is well-formed
278 ;;; and that all blocks in the loops are known blocks. We also mark each block
279 ;;; that we see so that we can do a check later to detect blocks that weren't
281 (declaim (ftype (function (loop (or loop null)) (values)) check-loop-consistency))
282 (defun check-loop-consistency (loop superior)
283 (unless (eq (loop-superior loop) superior)
284 (barf "wrong superior in ~S, should be ~S" loop superior))
286 (/= (loop-depth loop) (1+ (loop-depth superior))))
287 (barf "wrong depth in ~S" loop))
289 (dolist (tail (loop-tail loop))
290 (check-loop-block tail loop))
291 (dolist (exit (loop-exits loop))
292 (check-loop-block exit loop))
293 (check-loop-block (loop-head loop) loop)
294 (unless (eq (block-loop (loop-head loop)) loop)
295 (barf "The head of ~S is not directly in the loop." loop))
297 (do ((block (loop-blocks loop) (block-loop-next block)))
299 (setf (block-flag block) t)
300 (unless (gethash block *seen-blocks*)
301 (barf "unseen block ~S in Blocks for ~S" block loop))
302 (unless (eq (block-loop block) loop)
303 (barf "wrong loop in ~S, should be ~S" block loop)))
305 (dolist (inferior (loop-inferiors loop))
306 (check-loop-consistency inferior loop))
309 ;;; Check that Block is either in Loop or an inferior.
310 (declaim (ftype (function (block loop) (values)) check-loop-block))
311 (defun check-loop-block (block loop)
312 (unless (gethash block *seen-blocks*)
313 (barf "unseen block ~S in loop info for ~S" block loop))
315 (if (eq (block-loop block) l)
317 (dolist (inferior (loop-inferiors l) nil)
318 (when (walk inferior) (return t))))))
320 (barf "~S is in loop info for ~S but not in the loop." block loop)))
325 ;;; Check a block for consistency at the general flow-graph level, and
326 ;;; call CHECK-NODE-CONSISTENCY on each node to locally check for
327 ;;; semantic consistency.
328 (declaim (ftype (function (cblock) (values)) check-block-consistency))
329 (defun check-block-consistency (block)
331 (dolist (pred (block-pred block))
332 (unless (gethash pred *seen-blocks*)
333 (barf "unseen predecessor ~S in ~S" pred block))
334 (unless (member block (block-succ pred))
335 (barf "bad predecessor link ~S in ~S" pred block)))
337 (let* ((fun (block-home-lambda block))
338 (fun-deleted (eq (functional-kind fun) :deleted))
339 (this-ctran (block-start block))
340 (last (block-last block)))
342 (check-fun-reached fun block))
343 (when (not this-ctran)
344 (barf "~S has no START." block))
346 (barf "~S has no LAST." block))
347 (unless (eq (ctran-kind this-ctran) :block-start)
348 (barf "The START of ~S has the wrong kind." block))
350 (when (ctran-use this-ctran)
351 (barf "The ctran ~S is used." this-ctran))
353 (when (node-next last)
354 (barf "Last node ~S of ~S has next ctran." last block))
357 (unless (eq (ctran-block this-ctran) block)
358 (barf "BLOCK of ~S should be ~S." this-ctran block))
360 (let ((node (ctran-next this-ctran)))
361 (unless (node-p node)
362 (barf "~S has strange NEXT." this-ctran))
363 (unless (eq (node-prev node) this-ctran)
364 (barf "PREV in ~S should be ~S." node this-ctran))
366 (when (valued-node-p node)
367 (binding* ((lvar (node-lvar node) :exit-if-null))
368 (unless (memq node (find-uses lvar))
369 (barf "~S is not used by its LVAR ~S." node lvar))
370 (when (singleton-p (lvar-uses lvar))
371 (barf "~S has exactly 1 use, but LVAR-USES is a list."
373 (unless (lvar-dest lvar)
374 (barf "~S does not have dest." lvar))))
376 (check-node-reached node)
378 (check-node-consistency node))
380 (let ((next (node-next node)))
381 (when (and (not next) (not (eq node last)))
382 (barf "~S has no NEXT." node))
383 (when (eq node last) (return))
384 (unless (eq (ctran-kind next) :inside-block)
385 (barf "The interior ctran ~S in ~S has the wrong kind."
388 (unless (ctran-next next)
389 (barf "~S has no NEXT." next))
390 (unless (eq (ctran-use next) node)
391 (barf "USE in ~S should be ~S." next node))
392 (setq this-ctran next))))
394 (check-block-successors block))
397 ;;; Check that BLOCK is properly terminated. Each successor must be
398 ;;; accounted for by the type of the last node.
399 (declaim (ftype (function (cblock) (values)) check-block-successors))
400 (defun check-block-successors (block)
401 (let ((last (block-last block))
402 (succ (block-succ block)))
404 (let* ((comp (block-component block)))
406 (unless (gethash b *seen-blocks*)
407 (barf "unseen successor ~S in ~S" b block))
408 (unless (member block (block-pred b))
409 (barf "bad successor link ~S in ~S" b block))
410 (unless (eq (block-component b) comp)
411 (barf "The successor ~S in ~S is in a different component."
417 (unless (proper-list-of-length-p succ 1 2)
418 (barf "~S ends in an IF, but doesn't have one or two successors."
420 (unless (member (if-consequent last) succ)
421 (barf "The CONSEQUENT for ~S isn't in SUCC for ~S." last block))
422 (unless (member (if-alternative last) succ)
423 (barf "The ALTERNATIVE for ~S isn't in SUCC for ~S." last block)))
425 (unless (if (eq (functional-kind (return-lambda last)) :deleted)
427 (and (= (length succ) 1)
429 (component-tail (block-component block)))))
430 (barf "strange successors for RETURN in ~S" block)))
432 (unless (proper-list-of-length-p succ 0 1)
433 (barf "EXIT node with strange number of successors: ~S" last)))
435 (unless (or (= (length succ) 1) (node-tail-p last)
436 (and (block-delete-p block) (null succ)))
437 (barf "~S ends in normal node, but doesn't have one successor."
441 ;;;; node consistency checking
443 ;;; Check that the DEST for LVAR is the specified NODE. We also mark
444 ;;; the block LVAR is in as SEEN.
445 #+nil(declaim (ftype (function (lvar node) (values)) check-dest))
446 (defun check-dest (lvar node)
448 (unless (gethash (node-block use) *seen-blocks*)
449 (barf "Node ~S using ~S is in an unknown block." use lvar)))
450 (unless (eq (lvar-dest lvar) node)
451 (barf "DEST for ~S should be ~S." lvar node))
452 (unless (find-uses lvar)
453 (barf "Lvar ~S has a destinatin, but no uses."
457 ;;; This function deals with checking for consistency of the
458 ;;; type-dependent information in a node.
459 (defun check-node-consistency (node)
460 (declare (type node node))
463 (let ((leaf (ref-leaf node)))
464 (when (functional-p leaf)
465 (if (eq (functional-kind leaf) :toplevel-xep)
466 (unless (component-toplevelish-p (block-component (node-block node)))
467 (barf ":TOPLEVEL-XEP ref in non-top-level component: ~S"
469 (check-fun-reached leaf node)))))
471 (check-dest (basic-combination-fun node) node)
472 (when (and (mv-combination-p node)
473 (eq (basic-combination-kind node) :local))
474 (let ((fun-lvar (basic-combination-fun node)))
475 (unless (ref-p (lvar-uses fun-lvar))
476 (barf "function in a local mv-combination is not a LEAF: ~S" node))
477 (let ((fun (ref-leaf (lvar-use fun-lvar))))
478 (unless (lambda-p fun)
479 (barf "function ~S in a local mv-combination ~S is not local"
481 (unless (eq (functional-kind fun) :mv-let)
482 (barf "function ~S in a local mv-combination ~S is not of kind :MV-LET"
484 (dolist (arg (basic-combination-args node))
486 (arg (check-dest arg node))
487 ((not (and (eq (basic-combination-kind node) :local)
488 (combination-p node)))
489 (barf "flushed arg not in local call: ~S" node))
492 ;; KLUDGE: In sbcl-0.6.11.37, the compiler doesn't like
493 ;; (DECLARE (TYPE INDEX POS)) after the inline expansion of
494 ;; POSITION. It compiles it correctly, but it issues a type
495 ;; mismatch warning because it can't eliminate the
496 ;; possibility that control will flow through the
497 ;; NIL-returning branch. So we punt here. -- WHN 2001-04-15
498 (declare (notinline position))
499 (let ((fun (ref-leaf (lvar-use
500 (basic-combination-fun node))))
501 (pos (position arg (basic-combination-args node))))
502 (declare (type index pos))
503 (when (leaf-refs (elt (lambda-vars fun) pos))
504 (barf "flushed arg for referenced var in ~S" node)))))))
505 (let* ((lvar (node-lvar node))
506 (dest (and lvar (lvar-dest lvar))))
507 (when (and (return-p dest)
508 (eq (basic-combination-kind node) :local)
509 (not (eq (lambda-tail-set (combination-lambda node))
510 (lambda-tail-set (return-lambda dest)))))
511 (barf "tail local call to function with different tail set:~% ~S"
514 (check-dest (if-test node) node)
515 (unless (eq (block-last (node-block node)) node)
516 (barf "IF not at block end: ~S" node)))
518 (check-dest (set-value node) node))
520 (check-dest (cast-value node) node))
522 (check-fun-reached (bind-lambda node) node))
524 (check-fun-reached (return-lambda node) node)
525 (check-dest (return-result node) node)
526 (unless (eq (block-last (node-block node)) node)
527 (barf "RETURN not at block end: ~S" node)))
529 (unless (member node (lambda-entries (node-home-lambda node)))
530 (barf "~S is not in ENTRIES for its home LAMBDA." node))
531 (dolist (exit (entry-exits node))
532 (unless (node-deleted exit)
533 (check-node-reached node))))
535 (let ((entry (exit-entry node))
536 (value (exit-value node)))
538 (check-node-reached entry)
539 (unless (member node (entry-exits entry))
540 (barf "~S is not in its ENTRY's EXITS." node))
542 (check-dest value node)))
545 (barf "~S has VALUE but no ENTRY." node)))))))
549 ;;;; IR2 consistency checking
551 ;;; Check for some kind of consistency in some REFs linked together by
552 ;;; TN-REF-ACROSS. VOP is the VOP that the references are in. WRITE-P
553 ;;; is the value of WRITE-P that should be present. COUNT is the
554 ;;; minimum number of operands expected. If MORE-P is true, then any
555 ;;; larger number will also be accepted. WHAT is a string describing
556 ;;; the kind of operand in error messages.
557 (defun check-tn-refs (refs vop write-p count more-p what)
558 (let ((vop-refs (vop-refs vop)))
559 (do ((ref refs (tn-ref-across ref))
563 (barf "There should be at least ~W ~A in ~S, but there are only ~W."
565 (when (and (not more-p) (> num count))
566 (barf "There should be ~W ~A in ~S, but are ~W."
567 count what vop num)))
568 (unless (eq (tn-ref-vop ref) vop)
569 (barf "VOP is ~S isn't ~S." ref vop))
570 (unless (eq (tn-ref-write-p ref) write-p)
571 (barf "The WRITE-P in ~S isn't ~S." vop write-p))
572 (unless (find-in #'tn-ref-next-ref ref vop-refs)
573 (barf "~S not found in REFS for ~S" ref vop))
574 (unless (find-in #'tn-ref-next ref
575 (if (tn-ref-write-p ref)
576 (tn-writes (tn-ref-tn ref))
577 (tn-reads (tn-ref-tn ref))))
578 (barf "~S not found in reads/writes for its TN" ref))
580 (let ((target (tn-ref-target ref)))
582 (unless (eq (tn-ref-write-p target) (not (tn-ref-write-p ref)))
583 (barf "The target for ~S isn't complementary WRITE-P." ref))
584 (unless (find-in #'tn-ref-next-ref target vop-refs)
585 (barf "The target for ~S isn't in REFS for ~S." ref vop)))))))
587 ;;; Verify the sanity of the VOP-REFS slot in VOP. This involves checking
588 ;;; that each referenced TN appears as an argument, result or temp, and also
589 ;;; basic checks for the plausibility of the specified ordering of the refs.
590 (defun check-vop-refs (vop)
591 (declare (type vop vop))
592 (do ((ref (vop-refs vop) (tn-ref-next-ref ref)))
595 ((find-in #'tn-ref-across ref (vop-args vop)))
596 ((find-in #'tn-ref-across ref (vop-results vop)))
597 ((not (eq (tn-ref-vop ref) vop))
598 (barf "VOP in ~S isn't ~S." ref vop))
599 ((find-in #'tn-ref-across ref (vop-temps vop)))
600 ((tn-ref-write-p ref)
601 (barf "stray ref that isn't a READ: ~S" ref))
603 (let* ((tn (tn-ref-tn ref))
604 (temp (find-in #'tn-ref-across tn (vop-temps vop)
607 (barf "stray ref with no corresponding temp write: ~S" ref))
608 (unless (find-in #'tn-ref-next-ref temp (tn-ref-next-ref ref))
609 (barf "Read is after write for temp ~S in refs of ~S."
613 ;;; Check the basic sanity of the VOP linkage, then call some other
614 ;;; functions to check on the TN-REFS. We grab some info out of the
615 ;;; VOP-INFO to tell us what to expect.
617 ;;; [### Check that operand type restrictions are met?]
618 (defun check-ir2-block-consistency (2block)
619 (declare (type ir2-block 2block))
620 (do ((vop (ir2-block-start-vop 2block)
624 (unless (eq prev (ir2-block-last-vop 2block))
625 (barf "The last VOP in ~S should be ~S." 2block prev)))
626 (unless (eq (vop-prev vop) prev)
627 (barf "PREV in ~S should be ~S." vop prev))
629 (unless (eq (vop-block vop) 2block)
630 (barf "BLOCK in ~S should be ~S." vop 2block))
634 (let* ((info (vop-info vop))
635 (atypes (template-arg-types info))
636 (rtypes (template-result-types info)))
637 (check-tn-refs (vop-args vop) vop nil
638 (count-if-not (lambda (x)
640 (eq (car x) :constant)))
642 (template-more-args-type info) "args")
643 (check-tn-refs (vop-results vop) vop t
644 (if (template-conditional-p info) 0 (length rtypes))
645 (template-more-results-type info) "results")
646 (check-tn-refs (vop-temps vop) vop t 0 t "temps")
647 (unless (= (length (vop-codegen-info vop))
648 (template-info-arg-count info))
649 (barf "wrong number of codegen info args in ~S" vop))))
652 ;;; Check stuff about the IR2 representation of COMPONENT. This assumes the
653 ;;; sanity of the basic flow graph.
655 ;;; [### Also grovel global TN data structures? Assume pack not
656 ;;; done yet? Have separate CHECK-TN-CONSISTENCY for pre-pack and
657 ;;; CHECK-PACK-CONSISTENCY for post-pack?]
658 (defun check-ir2-consistency (component)
659 (declare (type component component))
660 (do-ir2-blocks (block component)
661 (check-ir2-block-consistency block))
664 ;;;; lifetime analysis checking
666 ;;; Dump some info about how many TNs there, and what the conflicts data
667 ;;; structures are like.
668 (defun pre-pack-tn-stats (component &optional (stream *standard-output*))
669 (declare (type component component))
679 (do-packed-tns (tn component)
680 (let ((reads (tn-reads tn))
681 (writes (tn-writes tn)))
682 (when (and reads writes
683 (not (tn-ref-next reads)) (not (tn-ref-next writes))
684 (eq (tn-ref-vop reads) (tn-ref-vop writes)))
688 (unless (or (tn-reads tn) (tn-writes tn))
690 (cond ((eq (tn-kind tn) :component)
692 ((tn-global-conflicts tn)
694 ((:environment :debug-environment) (incf environment))
696 (do ((conf (tn-global-conflicts tn)
697 (global-conflicts-next-tnwise conf)))
703 (do ((tn (ir2-component-constant-tns (component-info component))
709 "~%TNs: ~W local, ~W temps, ~W constant, ~W env, ~W comp, ~W global.~@
710 Wired: ~W, Unused: ~W. ~W block~:P, ~W global conflict~:P.~%"
711 local temps const environment comp global wired unused
712 (ir2-block-count component)
716 ;;; If the entry in Local-TNs for TN in BLOCK is :MORE, then do some checks
717 ;;; for the validity of the usage.
718 (defun check-more-tn-entry (tn block)
719 (let* ((vop (ir2-block-start-vop block))
720 (info (vop-info vop)))
721 (macrolet ((frob (more-p ops)
723 (find-in #'tn-ref-across tn (,ops vop)
725 (unless (and (eq vop (ir2-block-last-vop block))
726 (or (frob template-more-args-type vop-args)
727 (frob template-more-results-type vop-results)))
728 (barf "strange :MORE LTN entry for ~S in ~S" tn block))))
731 (defun check-tn-conflicts (component)
732 (do-packed-tns (tn component)
733 (unless (or (not (eq (tn-kind tn) :normal))
736 (barf "no references to ~S" tn))
738 (unless (tn-sc tn) (barf "~S has no SC." tn))
740 (let ((conf (tn-global-conflicts tn))
743 ((eq kind :component)
744 (unless (member tn (ir2-component-component-tns
745 (component-info component)))
746 (barf "~S not in COMPONENT-TNs for ~S" tn component)))
748 (do ((conf conf (global-conflicts-next-tnwise conf))
751 (unless (eq (global-conflicts-tn conf) tn)
752 (barf "TN in ~S should be ~S." conf tn))
754 (unless (eq (global-conflicts-kind conf) :live)
755 (let* ((block (global-conflicts-block conf))
756 (ltn (svref (ir2-block-local-tns block)
757 (global-conflicts-number conf))))
759 ((eq ltn :more) (check-more-tn-entry tn block))
761 (barf "~S wrong in LTN map for ~S" conf tn)))))
764 (unless (> (ir2-block-number (global-conflicts-block conf))
765 (ir2-block-number (global-conflicts-block prev)))
766 (barf "~s and ~s out of order" prev conf)))))
767 ((member (tn-kind tn) '(:constant :specified-save)))
769 (let ((local (tn-local tn)))
771 (barf "~S has no global conflicts, but isn't local either." tn))
772 (unless (eq (svref (ir2-block-local-tns local)
773 (tn-local-number tn))
775 (barf "~S wrong in LTN map" tn))
776 (do ((ref (tn-reads tn) (tn-ref-next ref)))
778 (unless (eq (vop-block (tn-ref-vop ref)) local)
779 (barf "~S has references in blocks other than its LOCAL block."
781 (do ((ref (tn-writes tn) (tn-ref-next ref)))
783 (unless (eq (vop-block (tn-ref-vop ref)) local)
784 (barf "~S has references in blocks other than its LOCAL block."
788 (defun check-block-conflicts (component)
789 (do-ir2-blocks (block component)
790 (do ((conf (ir2-block-global-tns block)
791 (global-conflicts-next-blockwise conf))
795 (unless (> (tn-number (global-conflicts-tn conf))
796 (tn-number (global-conflicts-tn prev)))
797 (barf "~S and ~S out of order in ~S" prev conf block)))
799 (unless (find-in #'global-conflicts-next-tnwise
802 (global-conflicts-tn conf)))
803 (barf "~S missing from global conflicts of its TN" conf)))
805 (let ((map (ir2-block-local-tns block)))
806 (dotimes (i (ir2-block-local-tn-count block))
807 (let ((tn (svref map i)))
808 (unless (or (eq tn :more)
810 (tn-global-conflicts tn)
811 (eq (tn-local tn) block))
812 (barf "strange TN ~S in LTN map for ~S" tn block)))))))
814 ;;; All TNs live at the beginning of an environment must be passing
815 ;;; locations associated with that environment. We make an exception
816 ;;; for wired TNs in XEP functions, since we randomly reference wired
817 ;;; TNs to access the full call passing locations.
818 (defun check-environment-lifetimes (component)
819 (dolist (fun (component-lambdas component))
820 (let* ((env (lambda-physenv fun))
821 (2env (physenv-info env))
822 (vars (lambda-vars fun))
823 (closure (ir2-physenv-closure 2env))
824 (pc (ir2-physenv-return-pc-pass 2env))
825 (fp (ir2-physenv-old-fp 2env))
826 (2block (block-info (lambda-block (physenv-lambda env)))))
827 (do ((conf (ir2-block-global-tns 2block)
828 (global-conflicts-next-blockwise conf)))
830 (let ((tn (global-conflicts-tn conf)))
831 (unless (or (eq (global-conflicts-kind conf) :write)
834 (and (xep-p fun) (tn-offset tn))
835 (member (tn-kind tn) '(:environment :debug-environment))
836 (member tn vars :key #'leaf-info)
837 (member tn closure :key #'cdr))
838 (barf "strange TN live at head of ~S: ~S" env tn))))))
841 ;;; Check for some basic sanity in the TN conflict data structures,
842 ;;; and also check that no TNs are unexpectedly live at environment
844 (defun check-life-consistency (component)
845 (check-tn-conflicts component)
846 (check-block-conflicts component)
847 (check-environment-lifetimes component))
849 ;;;; pack consistency checking
851 (defun check-pack-consistency (component)
852 (flet ((check (scs ops)
853 (do ((scs scs (cdr scs))
854 (op ops (tn-ref-across op)))
856 (let ((load-tn (tn-ref-load-tn op)))
857 (unless (eq (svref (car scs)
860 (or load-tn (tn-ref-tn op)))))
862 (barf "operand restriction not satisfied: ~S" op))))))
863 (do-ir2-blocks (block component)
864 (do ((vop (ir2-block-last-vop block) (vop-prev vop)))
866 (let ((info (vop-info vop)))
867 (check (vop-info-result-load-scs info) (vop-results vop))
868 (check (vop-info-arg-load-scs info) (vop-args vop))))))
871 ;;;; data structure dumping routines
873 ;;; When we print CONTINUATIONs and TNs, we assign them small numeric
874 ;;; IDs so that we can get a handle on anonymous objects given a
878 ;;; * Perhaps this machinery should be #!+SB-SHOW.
879 ;;; * Probably the hash tables should either be weak hash tables,
880 ;;; or only allocated within a single compilation unit. Otherwise
881 ;;; there will be a tendency for them to grow without bound and
882 ;;; keep garbage from being collected.
883 (macrolet ((def (counter vto vfrom fto ffrom)
885 (declaim (type hash-table ,vto ,vfrom))
886 (defvar ,vto (make-hash-table :test 'eq))
887 (defvar ,vfrom (make-hash-table :test 'eql))
888 (declaim (type fixnum ,counter))
893 (let ((num (incf ,counter)))
894 (setf (gethash num ,vfrom) x)
895 (setf (gethash x ,vto) num))))
898 (values (gethash num ,vfrom))))))
899 (def *continuation-number* *continuation-numbers* *number-continuations*
901 (def *tn-id* *tn-ids* *id-tns* tn-id id-tn)
902 (def *label-id* *id-labels* *label-ids* label-id id-label))
904 ;;; Print a terse one-line description of LEAF.
905 (defun print-leaf (leaf &optional (stream *standard-output*))
906 (declare (type leaf leaf) (type stream stream))
908 (lambda-var (prin1 (leaf-debug-name leaf) stream))
909 (constant (format stream "'~S" (constant-value leaf)))
911 (format stream "~S {~A}" (leaf-debug-name leaf) (global-var-kind leaf)))
913 (format stream "~S ~S" (type-of leaf) (functional-debug-name leaf)))))
915 ;;; Attempt to find a block given some thing that has to do with it.
916 (declaim (ftype (sfunction (t) cblock) block-or-lose))
917 (defun block-or-lose (thing)
920 (ir2-block (ir2-block-block thing))
921 (vop (block-or-lose (vop-block thing)))
922 (tn-ref (block-or-lose (tn-ref-vop thing)))
923 (ctran (ctran-block thing))
924 (node (node-block thing))
925 (component (component-head thing))
926 #| (cloop (loop-head thing))|#
927 (integer (ctran-block (num-cont thing)))
928 (functional (lambda-block (main-entry thing)))
929 (null (error "Bad thing: ~S." thing))
930 (symbol (block-or-lose (gethash thing *free-funs*)))))
933 (defun print-ctran (cont)
934 (declare (type ctran cont))
935 (format t "c~D " (cont-num cont))
937 (defun print-lvar (cont)
938 (declare (type lvar cont))
939 (format t "v~D " (cont-num cont))
942 (defun print-lvar-stack (stack &optional (stream *standard-output*))
943 (loop for (lvar . rest) on stack
944 do (format stream "~:[u~;d~]v~D~@[ ~]"
945 (lvar-dynamic-extent lvar) (cont-num lvar) rest)))
947 ;;; Print out the nodes in BLOCK in a format oriented toward
948 ;;; representing what the code does.
949 (defun print-nodes (block)
950 (setq block (block-or-lose block))
951 (pprint-logical-block (nil nil)
952 (format t "~:@_IR1 block ~D start c~D"
953 (block-number block) (cont-num (block-start block)))
954 (when (block-delete-p block)
955 (format t " <deleted>"))
957 (pprint-newline :mandatory)
958 (awhen (block-info block)
959 (format t "start stack: ")
960 (print-lvar-stack (ir2-block-start-stack it))
961 (pprint-newline :mandatory))
962 (do ((ctran (block-start block) (node-next (ctran-next ctran))))
964 (let ((node (ctran-next ctran)))
965 (format t "~3D>~:[ ~;~:*~3D:~] "
967 (when (and (valued-node-p node) (node-lvar node))
968 (cont-num (node-lvar node))))
970 (ref (print-leaf (ref-leaf node)))
972 (let ((kind (basic-combination-kind node)))
973 (format t "~(~A~A ~A~) "
974 (if (node-tail-p node) "tail " "")
977 (print-lvar (basic-combination-fun node))
978 (dolist (arg (basic-combination-args node))
981 (format t "<none> ")))))
983 (write-string "set ")
984 (print-leaf (set-var node))
986 (print-lvar (set-value node)))
989 (print-lvar (if-test node))
990 (print-ctran (block-start (if-consequent node)))
991 (print-ctran (block-start (if-alternative node))))
993 (write-string "bind ")
994 (print-leaf (bind-lambda node))
995 (when (functional-kind (bind-lambda node))
996 (format t " ~S ~S" :kind (functional-kind (bind-lambda node)))))
998 (write-string "return ")
999 (print-lvar (return-result node))
1000 (print-leaf (return-lambda node)))
1002 (let ((cleanup (entry-cleanup node)))
1003 (case (cleanup-kind cleanup)
1005 (format t "entry DX~{ v~D~}"
1006 (mapcar (lambda (lvar-or-cell)
1007 (if (consp lvar-or-cell)
1008 (cons (car lvar-or-cell)
1009 (cont-num (cdr lvar-or-cell)))
1010 (cont-num lvar-or-cell)))
1011 (cleanup-info cleanup))))
1013 (format t "entry ~S" (entry-exits node))))))
1015 (let ((value (exit-value node)))
1020 (format t "exit <no value>"))
1022 (format t "exit <degenerate>")))))
1024 (let ((value (cast-value node)))
1025 (format t "cast v~D ~A[~S -> ~S]" (cont-num value)
1026 (if (cast-%type-check node) #\+ #\-)
1027 (cast-type-to-check node)
1028 (cast-asserted-type node)))))
1029 (pprint-newline :mandatory)))
1031 (awhen (block-info block)
1032 (format t "end stack: ")
1033 (print-lvar-stack (ir2-block-end-stack it))
1034 (pprint-newline :mandatory))
1035 (let ((succ (block-succ block)))
1036 (format t "successors~{ c~D~}~%"
1037 (mapcar (lambda (x) (cont-num (block-start x))) succ))))
1040 ;;; Print the guts of a TN. (logic shared between PRINT-OBJECT (TN T)
1041 ;;; and printers for compound objects which contain TNs)
1042 (defun print-tn-guts (tn &optional (stream *standard-output*))
1043 (declare (type tn tn))
1044 (let ((leaf (tn-leaf tn)))
1046 (print-leaf leaf stream)
1047 (format stream "!~D" (tn-id tn)))
1049 (format stream "t~D" (tn-id tn))))
1050 (when (and (tn-sc tn) (tn-offset tn))
1051 (format stream "[~A]" (location-print-name tn)))))
1053 ;;; Print the TN-REFs representing some operands to a VOP, linked by
1055 (defun print-operands (refs)
1056 (declare (type (or tn-ref null) refs))
1057 (pprint-logical-block (*standard-output* nil)
1058 (do ((ref refs (tn-ref-across ref)))
1060 (let ((tn (tn-ref-tn ref))
1061 (ltn (tn-ref-load-tn ref)))
1066 (princ (if (tn-ref-write-p ref) #\< #\>))
1067 (print-tn-guts ltn)))
1069 (pprint-newline :fill)))))
1071 ;;; Print the VOP, putting args, info and results on separate lines, if
1073 (defun print-vop (vop)
1074 (pprint-logical-block (*standard-output* nil)
1075 (princ (vop-info-name (vop-info vop)))
1077 (pprint-indent :current 0)
1078 (print-operands (vop-args vop))
1079 (pprint-newline :linear)
1080 (when (vop-codegen-info vop)
1081 (princ (with-output-to-string (stream)
1082 (let ((*print-level* 1)
1084 (format stream "{~{~S~^ ~}} " (vop-codegen-info vop)))))
1085 (pprint-newline :linear))
1086 (when (vop-results vop)
1088 (print-operands (vop-results vop))))
1089 (pprint-newline :mandatory))
1091 ;;; Print the VOPs in the specified IR2 block.
1092 (defun print-ir2-block (block)
1093 (declare (type ir2-block block))
1094 (pprint-logical-block (*standard-output* nil)
1096 ((eq (block-info (ir2-block-block block)) block)
1097 (format t "~:@_IR2 block ~D start c~D~:@_"
1098 (ir2-block-number block)
1099 (cont-num (block-start (ir2-block-block block))))
1100 (let ((label (ir2-block-%label block)))
1102 (format t "L~D:~:@_" (label-id label)))))
1104 (format t "<overflow>~:@_")))
1106 (do ((vop (ir2-block-start-vop block)
1108 (number 0 (1+ number)))
1110 (format t "~W: " number)
1113 ;;; This is like PRINT-NODES, but dumps the IR2 representation of the
1115 (defun print-vops (block)
1116 (setq block (block-or-lose block))
1117 (let ((2block (block-info block)))
1118 (print-ir2-block 2block)
1119 (do ((b (ir2-block-next 2block) (ir2-block-next b)))
1120 ((not (eq (ir2-block-block b) block)))
1121 (print-ir2-block b)))
1124 ;;; Scan the IR2 blocks in emission order.
1125 (defun print-ir2-blocks (thing &optional full)
1126 (let* ((block (component-head (block-component (block-or-lose thing))))
1127 (2block (block-info block)))
1128 (pprint-logical-block (nil nil)
1130 do (setq block (ir2-block-block 2block))
1131 do (pprint-logical-block (*standard-output* nil)
1134 (format t "IR1 block ~D start c~D"
1135 (block-number block)
1136 (cont-num (block-start block))))
1137 (pprint-indent :block 4)
1138 (pprint-newline :mandatory)
1139 (loop while (and 2block (eq (ir2-block-block 2block) block))
1140 do (print-ir2-block 2block)
1141 do (setq 2block (ir2-block-next 2block))))
1142 do (pprint-newline :mandatory))))
1145 ;;; Do a PRINT-NODES on BLOCK and all blocks reachable from it by
1146 ;;; successor links.
1147 (defun print-blocks (block)
1148 (setq block (block-or-lose block))
1149 (do-blocks (block (block-component block) :both)
1150 (setf (block-flag block) nil))
1151 (labels ((walk (block)
1152 (unless (block-flag block)
1153 (setf (block-flag block) t)
1154 (when (block-start block)
1155 (print-nodes block))
1156 (dolist (block (block-succ block))
1161 ;;; Print all blocks in BLOCK's component in DFO.
1162 (defun print-all-blocks (thing)
1163 (do-blocks (block (block-component (block-or-lose thing)))
1164 (handler-case (print-nodes block)
1166 (format t "~&~A...~%" condition))))
1169 (defvar *list-conflicts-table* (make-hash-table :test 'eq))
1171 ;;; Add all ALWAYS-LIVE TNs in BLOCK to the conflicts. TN is ignored
1172 ;;; when it appears in the global conflicts.
1173 (defun add-always-live-tns (block tn)
1174 (declare (type ir2-block block) (type tn tn))
1175 (do ((conf (ir2-block-global-tns block)
1176 (global-conflicts-next-blockwise conf)))
1178 (when (eq (global-conflicts-kind conf) :live)
1179 (let ((btn (global-conflicts-tn conf)))
1181 (setf (gethash btn *list-conflicts-table*) t)))))
1184 ;;; Add all local TNs in BLOCK to the conflicts.
1185 (defun add-all-local-tns (block)
1186 (declare (type ir2-block block))
1187 (let ((ltns (ir2-block-local-tns block)))
1188 (dotimes (i (ir2-block-local-tn-count block))
1189 (setf (gethash (svref ltns i) *list-conflicts-table*) t)))
1192 ;;; Make a list out of all of the recorded conflicts.
1193 (defun listify-conflicts-table ()
1195 (maphash (lambda (k v)
1196 (declare (ignore v))
1199 *list-conflicts-table*)
1200 (clrhash *list-conflicts-table*)
1203 ;;; Return a list of a the TNs that conflict with TN. Sort of, kind
1204 ;;; of. For debugging use only. Probably doesn't work on :COMPONENT TNs.
1205 (defun list-conflicts (tn)
1206 (aver (member (tn-kind tn) '(:normal :environment :debug-environment)))
1207 (let ((confs (tn-global-conflicts tn)))
1209 (clrhash *list-conflicts-table*)
1210 (do ((conf confs (global-conflicts-next-tnwise conf)))
1212 (format t "~&#<block ~D kind ~S>~%"
1213 (block-number (ir2-block-block (global-conflicts-block
1215 (global-conflicts-kind conf))
1216 (let ((block (global-conflicts-block conf)))
1217 (add-always-live-tns block tn)
1218 (if (eq (global-conflicts-kind conf) :live)
1219 (add-all-local-tns block)
1220 (let ((bconf (global-conflicts-conflicts conf))
1221 (ltns (ir2-block-local-tns block)))
1222 (dotimes (i (ir2-block-local-tn-count block))
1223 (when (/= (sbit bconf i) 0)
1224 (setf (gethash (svref ltns i) *list-conflicts-table*)
1226 (listify-conflicts-table))
1228 (let* ((block (tn-local tn))
1229 (ltns (ir2-block-local-tns block))
1230 (confs (tn-local-conflicts tn)))
1232 (dotimes (i (ir2-block-local-tn-count block))
1233 (when (/= (sbit confs i) 0)
1234 (let ((tn (svref ltns i)))
1235 (when (and tn (not (eq tn :more))
1236 (not (tn-global-conflicts tn)))
1238 (do ((gtn (ir2-block-global-tns block)
1239 (global-conflicts-next-blockwise gtn)))
1241 (when (or (eq (global-conflicts-kind gtn) :live)
1242 (/= (sbit confs (global-conflicts-number gtn)) 0))
1243 (res (global-conflicts-tn gtn))))
1246 (defun nth-vop (thing n)
1248 "Return the Nth VOP in the IR2-BLOCK pointed to by THING."
1249 (let ((block (block-info (block-or-lose thing))))
1251 (vop (ir2-block-start-vop block) (vop-next vop)))