Initial revision
[sbcl.git] / src / compiler / debug.lisp
1 ;;;; This file contains utilities for debugging the compiler --
2 ;;;; currently only stuff for checking the consistency of the IR1.
3
4 ;;;; This software is part of the SBCL system. See the README file for
5 ;;;; more information.
6 ;;;;
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.
12
13 (in-package "SB!C")
14
15 (file-comment
16   "$Header$")
17
18 (defvar *args* ()
19   #!+sb-doc
20   "This variable is bound to the format arguments when an error is signalled
21   by BARF or BURP.")
22
23 (defvar *ignored-errors* (make-hash-table :test 'equal))
24
25 ;;; A definite inconsistency has been detected. Signal an error with
26 ;;; *args* bound to the list of the format args.
27 (declaim (ftype (function (string &rest t) (values)) barf))
28 (defun barf (string &rest *args*)
29   (unless (gethash string *ignored-errors*)
30     (restart-case
31         (apply #'error string *args*)
32       (continue ()
33         :report "Ignore this error.")
34       (ignore-all ()
35         :report "Ignore this and all future occurrences of this error."
36         (setf (gethash string *ignored-errors*) t))))
37   (values))
38
39 (defvar *burp-action* :warn
40   #!+sb-doc
41   "Action taken by the BURP function when a possible compiler bug is detected.
42   One of :WARN, :ERROR or :NONE.")
43 (declaim (type (member :warn :error :none) *burp-action*))
44
45 ;;; Called when something funny but possibly correct is noticed. Otherwise
46 ;;; similar to Barf.
47 (declaim (ftype (function (string &rest t) (values)) burp))
48 (defun burp (string &rest *args*)
49   (ecase *burp-action*
50     (:warn (apply #'warn string *args*))
51     (:error (apply #'cerror "press on anyway." string *args*))
52     (:none))
53   (values))
54
55 ;;; *Seen-Blocks* is a hashtable with true values for all blocks which appear
56 ;;; in the DFO for one of the specified components.
57 (defvar *seen-blocks* (make-hash-table :test 'eq))
58
59 ;;; *Seen-Functions* is similar, but records all the lambdas we reached by
60 ;;; recursing on top-level functions.
61 (defvar *seen-functions* (make-hash-table :test 'eq))
62
63 ;;; Barf if Node is in a block which wasn't reached during the graph walk.
64 (declaim (ftype (function (node) (values)) check-node-reached))
65 (defun check-node-reached (node)
66   (unless (gethash (continuation-block (node-prev node)) *seen-blocks*)
67     (barf "~S was not reached." node))
68   (values))
69
70 ;;; Check everything that we can think of for consistency. When a definite
71 ;;; inconsistency is detected, we BARF. Possible problems just cause us to
72 ;;; BURP. Our argument is a list of components, but we also look at the
73 ;;; *FREE-VARIABLES*, *FREE-FUNCTIONS* and *CONSTANTS*.
74 ;;;
75 ;;; First we do a pre-pass which finds all the blocks and lambdas, testing
76 ;;; that they are linked together properly and entering them in hashtables.
77 ;;; Next, we iterate over the blocks again, looking at the actual code and
78 ;;; control flow. Finally, we scan the global leaf hashtables, looking for
79 ;;; lossage.
80 (declaim (ftype (function (list) (values)) check-ir1-consistency))
81 (defun check-ir1-consistency (components)
82   (clrhash *seen-blocks*)
83   (clrhash *seen-functions*)
84   (dolist (c components)
85     (let* ((head (component-head c))
86            (tail (component-tail c)))
87       (unless (and (null (block-pred head)) (null (block-succ tail)))
88         (barf "~S is malformed." c))
89
90       (do ((prev nil block)
91            (block head (block-next block)))
92           ((null block)
93            (unless (eq prev tail)
94              (barf "wrong Tail for DFO, ~S in ~S" prev c)))
95         (setf (gethash block *seen-blocks*) t)
96         (unless (eq (block-prev block) prev)
97           (barf "bad PREV for ~S, should be ~S" block prev))
98         (unless (or (eq block tail)
99                     (eq (block-component block) c))
100           (barf "~S is not in ~S." block c)))
101 #|
102       (when (or (loop-blocks c) (loop-inferiors c))
103         (do-blocks (block c :both)
104           (setf (block-flag block) nil))
105         (check-loop-consistency c nil)
106         (do-blocks (block c :both)
107           (unless (block-flag block)
108             (barf "~S was not in any loop." block))))
109 |#
110     ))
111
112   (check-function-consistency components)
113
114   (dolist (c components)
115     (do ((block (block-next (component-head c)) (block-next block)))
116         ((null (block-next block)))
117       (check-block-consistency block)))
118
119   (maphash #'(lambda (k v)
120                (declare (ignore k))
121                (unless (or (constant-p v)
122                            (and (global-var-p v)
123                                 (member (global-var-kind v)
124                                         '(:global :special :constant))))
125                  (barf "strange *FREE-VARIABLES* entry: ~S" v))
126                (dolist (n (leaf-refs v))
127                  (check-node-reached n))
128                (when (basic-var-p v)
129                  (dolist (n (basic-var-sets v))
130                    (check-node-reached n))))
131            *free-variables*)
132
133   (maphash #'(lambda (k v)
134                (declare (ignore k))
135                (unless (constant-p v)
136                  (barf "strange *CONSTANTS* entry: ~S" v))
137                (dolist (n (leaf-refs v))
138                  (check-node-reached n)))
139            *constants*)
140
141   (maphash #'(lambda (k v)
142                (declare (ignore k))
143                (unless (or (functional-p v)
144                            (and (global-var-p v)
145                                 (eq (global-var-kind v) :global-function)))
146                  (barf "strange *FREE-FUNCTIONS* entry: ~S" v))
147                (dolist (n (leaf-refs v))
148                  (check-node-reached n)))
149            *free-functions*)
150   (clrhash *seen-functions*)
151   (clrhash *seen-blocks*)
152   (values))
153 \f
154 ;;;; function consistency checking
155
156 (defun observe-functional (x)
157   (declare (type functional x))
158   (when (gethash x *seen-functions*)
159     (barf "~S was seen more than once." x))
160   (unless (eq (functional-kind x) :deleted)
161     (setf (gethash x *seen-functions*) t)))
162
163 ;;; Check that the specified function has been seen.
164 (defun check-function-reached (fun where)
165   (declare (type functional fun))
166   (unless (gethash fun *seen-functions*)
167     (barf "unseen function ~S in ~S" fun where)))
168
169 ;;; In a lambda, check that the associated nodes are in seen blocks. In an
170 ;;; optional dispatch, check that the entry points were seen. If the function
171 ;;; is deleted, ignore it.
172 (defun check-function-stuff (functional)
173   (ecase (functional-kind functional)
174     (:external
175      (let ((fun (functional-entry-function functional)))
176        (check-function-reached fun functional)
177        (when (functional-kind fun)
178          (barf "The function for XEP ~S has kind." functional))
179        (unless (eq (functional-entry-function fun) functional)
180          (barf "bad back-pointer in function for XEP ~S" functional))))
181     ((:let :mv-let :assignment)
182      (check-function-reached (lambda-home functional) functional)
183      (when (functional-entry-function functional)
184        (barf "The LET ~S has entry function." functional))
185      (unless (member functional (lambda-lets (lambda-home functional)))
186        (barf "The LET ~S is not in LETs for HOME." functional))
187      (unless (eq (functional-kind functional) :assignment)
188        (when (rest (leaf-refs functional))
189          (barf "The LET ~S has multiple references." functional)))
190      (when (lambda-lets functional)
191        (barf "LETs in a LET: ~S" functional)))
192     (:optional
193      (when (functional-entry-function functional)
194        (barf ":OPTIONAL ~S has an ENTRY-FUNCTION." functional))
195      (let ((ef (lambda-optional-dispatch functional)))
196        (check-function-reached ef functional)
197        (unless (or (member functional (optional-dispatch-entry-points ef))
198                    (eq functional (optional-dispatch-more-entry ef))
199                    (eq functional (optional-dispatch-main-entry ef)))
200          (barf ":OPTIONAL ~S is not an e-p for its OPTIONAL-DISPATCH ~S."
201                functional ef))))
202     (:top-level
203      (unless (eq (functional-entry-function functional) functional)
204        (barf "The ENTRY-FUNCTION in ~S isn't a self-pointer." functional)))
205     ((nil :escape :cleanup)
206      (let ((ef (functional-entry-function functional)))
207        (when ef
208          (check-function-reached ef functional)
209          (unless (eq (functional-kind ef) :external)
210            (barf "The ENTRY-FUNCTION in ~S isn't an XEP: ~S."
211                  functional
212                  ef)))))
213     (:deleted
214      (return-from check-function-stuff)))
215
216   (case (functional-kind functional)
217     ((nil :optional :external :top-level :escape :cleanup)
218      (when (lambda-p functional)
219        (dolist (fun (lambda-lets functional))
220          (unless (eq (lambda-home fun) functional)
221            (barf "The home in ~S is not ~S." fun functional))
222          (check-function-reached fun functional))
223        (unless (eq (lambda-home functional) functional)
224          (barf "home not self-pointer in ~S" functional)))))
225
226   (etypecase functional
227     (clambda
228      (when (lambda-bind functional)
229        (check-node-reached (lambda-bind functional)))
230      (when (lambda-return functional)
231        (check-node-reached (lambda-return functional)))
232
233      (dolist (var (lambda-vars functional))
234        (dolist (ref (leaf-refs var))
235          (check-node-reached ref))
236        (dolist (set (basic-var-sets var))
237          (check-node-reached set))
238        (unless (eq (lambda-var-home var) functional)
239          (barf "HOME in ~S should be ~S." var functional))))
240     (optional-dispatch
241      (dolist (ep (optional-dispatch-entry-points functional))
242        (check-function-reached ep functional))
243      (let ((more (optional-dispatch-more-entry functional)))
244        (when more (check-function-reached more functional)))
245      (check-function-reached (optional-dispatch-main-entry functional)
246                              functional))))
247
248 (defun check-function-consistency (components)
249   (dolist (c components)
250     (dolist (fun (component-new-functions c))
251       (observe-functional fun))
252     (dolist (fun (component-lambdas c))
253       (when (eq (functional-kind fun) :external)
254         (let ((ef (functional-entry-function fun)))
255           (when (optional-dispatch-p ef)
256             (observe-functional ef))))
257       (observe-functional fun)
258       (dolist (let (lambda-lets fun))
259         (observe-functional let))))
260
261   (dolist (c components)
262     (dolist (fun (component-new-functions c))
263       (check-function-stuff fun))
264     (dolist (fun (component-lambdas c))
265       (when (eq (functional-kind fun) :deleted)
266         (barf "deleted lambda ~S in Lambdas for ~S" fun c))
267       (check-function-stuff fun)
268       (dolist (let (lambda-lets fun))
269         (check-function-stuff let)))))
270 \f
271 ;;;; loop consistency checking
272
273 #|
274 ;;; Descend through the loop nesting and check that the tree is well-formed
275 ;;; and that all blocks in the loops are known blocks. We also mark each block
276 ;;; that we see so that we can do a check later to detect blocks that weren't
277 ;;; in any loop.
278 (declaim (ftype (function (loop (or loop null)) (values)) check-loop-consistency))
279 (defun check-loop-consistency (loop superior)
280   (unless (eq (loop-superior loop) superior)
281     (barf "wrong superior in ~S, should be ~S" loop superior))
282   (when (and superior
283              (/= (loop-depth loop) (1+ (loop-depth superior))))
284     (barf "wrong depth in ~S" loop))
285
286   (dolist (tail (loop-tail loop))
287     (check-loop-block tail loop))
288   (dolist (exit (loop-exits loop))
289     (check-loop-block exit loop))
290   (check-loop-block (loop-head loop) loop)
291   (unless (eq (block-loop (loop-head loop)) loop)
292     (barf "The head of ~S is not directly in the loop." loop))
293
294   (do ((block (loop-blocks loop) (block-loop-next block)))
295       ((null block))
296     (setf (block-flag block) t)
297     (unless (gethash block *seen-blocks*)
298       (barf "unseen block ~S in Blocks for ~S" block loop))
299     (unless (eq (block-loop block) loop)
300       (barf "wrong loop in ~S, should be ~S" block loop)))
301
302   (dolist (inferior (loop-inferiors loop))
303     (check-loop-consistency inferior loop))
304   (values))
305
306 ;;; Check that Block is either in Loop or an inferior.
307 (declaim (ftype (function (block loop) (values)) check-loop-block))
308 (defun check-loop-block (block loop)
309   (unless (gethash block *seen-blocks*)
310     (barf "unseen block ~S in loop info for ~S" block loop))
311   (labels ((walk (l)
312              (if (eq (block-loop block) l)
313                  t
314                  (dolist (inferior (loop-inferiors l) nil)
315                    (when (walk inferior) (return t))))))
316     (unless (walk loop)
317       (barf "~S is in loop info for ~S but not in the loop." block loop)))
318   (values))
319
320 |#
321
322 ;;; Check a block for consistency at the general flow-graph level, and call
323 ;;; Check-Node-Consistency on each node to locally check for semantic
324 ;;; consistency.
325 (declaim (ftype (function (cblock) (values)) check-block-consistency))
326 (defun check-block-consistency (block)
327
328   (dolist (pred (block-pred block))
329     (unless (gethash pred *seen-blocks*)
330       (barf "unseen predecessor ~S in ~S" pred block))
331     (unless (member block (block-succ pred))
332       (barf "bad predecessor link ~S in ~S" pred block)))
333
334   (let* ((fun (block-home-lambda block))
335          (fun-deleted (eq (functional-kind fun) :deleted))
336          (this-cont (block-start block))
337          (last (block-last block)))
338     (unless fun-deleted
339       (check-function-reached fun block))
340     (when (not this-cont)
341       (barf "~S has no START." block))
342     (when (not last)
343       (barf "~S has no LAST." block))
344     (unless (eq (continuation-kind this-cont) :block-start)
345       (barf "The START of ~S has the wrong kind." block))
346
347     (let ((use (continuation-use this-cont))
348           (uses (block-start-uses block)))
349       (when (and (null use) (= (length uses) 1))
350         (barf "~S has a unique use, but no USE." this-cont))
351       (dolist (node uses)
352         (unless (eq (node-cont node) this-cont)
353           (barf "The USE ~S for START in ~S has wrong CONT." node block))
354         (check-node-reached node)))
355
356     (let* ((last-cont (node-cont last))
357            (cont-block (continuation-block last-cont))
358            (dest (continuation-dest last-cont)))
359       (ecase (continuation-kind last-cont)
360         (:deleted)
361         (:deleted-block-start
362          (let ((dest (continuation-dest last-cont)))
363            (when dest
364              (check-node-reached dest)))
365          (unless (member last (block-start-uses cont-block))
366            (barf "LAST in ~S is missing from uses of its Cont." block)))
367         (:block-start
368          (check-node-reached (continuation-next last-cont))
369          (unless (member last (block-start-uses cont-block))
370            (barf "LAST in ~S is missing from uses of its Cont." block)))
371         (:inside-block
372          (unless (eq cont-block block)
373            (barf "CONT of LAST in ~S is in a different BLOCK." block))
374          (unless (eq (continuation-use last-cont) last)
375            (barf "USE is not LAST in CONT of LAST in ~S." block))
376          (when (continuation-next last-cont)
377            (barf "CONT of LAST has a NEXT in ~S." block))))
378
379       (when dest
380         (check-node-reached dest)))
381
382     (loop       
383       (unless (eq (continuation-block this-cont) block)
384         (barf "BLOCK in ~S should be ~S." this-cont block))
385
386       (let ((dest (continuation-dest this-cont)))
387         (when dest
388           (check-node-reached dest)))
389
390       (let ((node (continuation-next this-cont)))
391         (unless (node-p node)
392           (barf "~S has strange NEXT." this-cont))
393         (unless (eq (node-prev node) this-cont)
394           (barf "PREV in ~S should be ~S." node this-cont))
395
396         (unless fun-deleted
397           (check-node-consistency node))
398         
399         (let ((cont (node-cont node)))
400           (when (not cont)
401             (barf "~S has no CONT." node))
402           (when (eq node last) (return))
403           (unless (eq (continuation-kind cont) :inside-block)
404             (barf "The interior continuation ~S in ~S has the wrong kind."
405                   cont
406                   block))
407           (unless (continuation-next cont)
408             (barf "~S has no NEXT." cont))
409           (unless (eq (continuation-use cont) node)
410             (barf "USE in ~S should be ~S." cont node))
411           (setq this-cont cont))))
412         
413     (check-block-successors block))
414   (values))
415
416 ;;; Check that Block is properly terminated. Each successor must be
417 ;;; accounted for by the type of the last node.
418 (declaim (ftype (function (cblock) (values)) check-block-successors))
419 (defun check-block-successors (block)
420   (let ((last (block-last block))
421         (succ (block-succ block)))
422
423     (let* ((comp (block-component block)))
424       (dolist (b succ)
425         (unless (gethash b *seen-blocks*)
426           (barf "unseen successor ~S in ~S" b block))
427         (unless (member block (block-pred b))
428           (barf "bad successor link ~S in ~S" b block))
429         (unless (eq (block-component b) comp)
430           (barf "The successor ~S in ~S is in a different component."
431                 b
432                 block))))
433
434     (typecase last
435       (cif
436        (unless (proper-list-of-length-p succ 1 2)
437          (barf "~S ends in an IF, but doesn't have one or two succesors."
438                block))
439        (unless (member (if-consequent last) succ)
440          (barf "The CONSEQUENT for ~S isn't in SUCC for ~S." last block))
441        (unless (member (if-alternative last) succ)
442          (barf "The ALTERNATIVE for ~S isn't in SUCC for ~S." last block)))
443       (creturn
444        (unless (if (eq (functional-kind (return-lambda last)) :deleted)
445                    (null succ)
446                    (and (= (length succ) 1)
447                         (eq (first succ)
448                             (component-tail (block-component block)))))
449          (barf "strange successors for RETURN in ~S" block)))
450       (exit
451        (unless (proper-list-of-length-p succ 0 1)
452          (barf "EXIT node with strange number of successors: ~S" last)))
453       (t
454        (unless (or (= (length succ) 1) (node-tail-p last)
455                    (and (block-delete-p block) (null succ)))
456          (barf "~S ends in normal node, but doesn't have one successor."
457                block)))))
458   (values))
459 \f
460 ;;;; node consistency checking
461
462 ;;; Check that the Dest for Cont is the specified Node. We also mark the
463 ;;; block Cont is in as Seen.
464 (declaim (ftype (function (continuation node) (values)) check-dest))
465 (defun check-dest (cont node)
466   (let ((kind (continuation-kind cont)))
467     (ecase kind
468       (:deleted
469        (unless (block-delete-p (node-block node))
470          (barf "DEST ~S of deleted continuation ~S is not DELETE-P."
471                cont node)))
472       (:deleted-block-start
473        (unless (eq (continuation-dest cont) node)
474          (barf "DEST for ~S should be ~S." cont node)))
475       ((:inside-block :block-start)
476        (unless (gethash (continuation-block cont) *seen-blocks*)
477          (barf "~S receives ~S, which is in an unknown block." node cont))
478        (unless (eq (continuation-dest cont) node)
479          (barf "DEST for ~S should be ~S." cont node)))))
480   (values))
481
482 ;;; This function deals with checking for consistency the type-dependent
483 ;;; information in a node.
484 (defun check-node-consistency (node)
485   (declare (type node node))
486   (etypecase node
487     (ref
488      (let ((leaf (ref-leaf node)))
489        (when (functional-p leaf)
490          (if (eq (functional-kind leaf) :top-level-xep)
491              (unless (eq (component-kind (block-component (node-block node)))
492                          :top-level)
493                (barf ":TOP-LEVEL-XEP ref in non-top-level component: ~S"
494                      node))
495              (check-function-reached leaf node)))))
496     (basic-combination
497      (check-dest (basic-combination-fun node) node)
498      (dolist (arg (basic-combination-args node))
499        (cond
500         (arg (check-dest arg node))
501         ((not (and (eq (basic-combination-kind node) :local)
502                    (combination-p node)))
503          (barf "flushed arg not in local call: ~S" node))
504         (t
505          (let ((fun (ref-leaf (continuation-use
506                                (basic-combination-fun node))))
507                (pos (position arg (basic-combination-args node))))
508            (check-type pos fixnum) ; to suppress warning -- WHN 19990311
509            (when (leaf-refs (elt (lambda-vars fun) pos))
510              (barf "flushed arg for referenced var in ~S" node))))))
511
512      (let ((dest (continuation-dest (node-cont node))))
513        (when (and (return-p dest)
514                   (eq (basic-combination-kind node) :local)
515                   (not (eq (lambda-tail-set (combination-lambda node))
516                            (lambda-tail-set (return-lambda dest)))))
517          (barf "tail local call to function with different tail set:~%  ~S"
518                node))))
519     (cif
520      (check-dest (if-test node) node)
521      (unless (eq (block-last (node-block node)) node)
522        (barf "IF not at block end: ~S" node)))
523     (cset
524      (check-dest (set-value node) node))
525     (bind
526      (check-function-reached (bind-lambda node) node))
527     (creturn
528      (check-function-reached (return-lambda node) node)
529      (check-dest (return-result node) node)
530      (unless (eq (block-last (node-block node)) node)
531        (barf "RETURN not at block end: ~S" node)))
532     (entry
533      (unless (member node (lambda-entries (node-home-lambda node)))
534        (barf "~S is not in ENTRIES for its home LAMBDA." node))
535      (dolist (exit (entry-exits node))
536        (unless (node-deleted exit)
537          (check-node-reached node))))
538     (exit
539      (let ((entry (exit-entry node))
540            (value (exit-value node)))
541        (cond (entry
542               (check-node-reached entry)
543               (unless (member node (entry-exits entry))
544                 (barf "~S is not in its ENTRY's EXITS." node))
545               (when value
546                 (check-dest value node)))
547              (t
548               (when value
549                 (barf "~S has VALUE but no ENTRY." node)))))))
550
551   (values))
552 \f
553 ;;;; IR2 consistency checking
554
555 ;;; Check for some kind of consistency in some Refs linked together by
556 ;;; TN-Ref-Across. VOP is the VOP that the references are in. Write-P is the
557 ;;; value of Write-P that should be present. Count is the minimum number of
558 ;;; operands expected. If More-P is true, then any larger number will also be
559 ;;; accepted. What is a string describing the kind of operand in error
560 ;;; messages.
561 (defun check-tn-refs (refs vop write-p count more-p what)
562   (let ((vop-refs (vop-refs vop)))
563     (do ((ref refs (tn-ref-across ref))
564          (num 0 (1+ num)))
565         ((null ref)
566          (when (< num count)
567            (barf "There should be at least ~D ~A in ~S, but are only ~D."
568                  count what vop num))
569          (when (and (not more-p) (> num count))
570            (barf "There should be ~D ~A in ~S, but are ~D."
571                  count what vop num)))
572       (unless (eq (tn-ref-vop ref) vop)
573         (barf "VOP is ~S isn't ~S." ref vop))
574       (unless (eq (tn-ref-write-p ref) write-p)
575         (barf "The WRITE-P in ~S isn't ~S." vop write-p))
576       (unless (find-in #'tn-ref-next-ref ref vop-refs)
577         (barf "~S not found in REFS for ~S" ref vop))
578       (unless (find-in #'tn-ref-next ref
579                        (if (tn-ref-write-p ref)
580                            (tn-writes (tn-ref-tn ref))
581                            (tn-reads (tn-ref-tn ref))))
582         (barf "~S not found in reads/writes for its TN" ref))
583
584       (let ((target (tn-ref-target ref)))
585         (when target
586           (unless (eq (tn-ref-write-p target) (not (tn-ref-write-p ref)))
587             (barf "The target for ~S isn't complementary WRITE-P." ref))
588           (unless (find-in #'tn-ref-next-ref target vop-refs)
589             (barf "The target for ~S isn't in REFS for ~S." ref vop)))))))
590
591 ;;; Verify the sanity of the VOP-Refs slot in VOP. This involves checking
592 ;;; that each referenced TN appears as an argument, result or temp, and also
593 ;;; basic checks for the plausibility of the specified ordering of the refs.
594 (defun check-vop-refs (vop)
595   (declare (type vop vop))
596   (do ((ref (vop-refs vop) (tn-ref-next-ref ref)))
597       ((null ref))
598     (cond
599      ((find-in #'tn-ref-across ref (vop-args vop)))
600      ((find-in #'tn-ref-across ref (vop-results vop)))
601      ((not (eq (tn-ref-vop ref) vop))
602       (barf "VOP in ~S isn't ~S." ref vop))
603      ((find-in #'tn-ref-across ref (vop-temps vop)))
604      ((tn-ref-write-p ref)
605       (barf "stray ref that isn't a READ: ~S" ref))
606      (t
607       (let* ((tn (tn-ref-tn ref))
608              (temp (find-in #'tn-ref-across tn (vop-temps vop)
609                             :key #'tn-ref-tn)))
610         (unless temp
611           (barf "stray ref with no corresponding temp write: ~S" ref))
612         (unless (find-in #'tn-ref-next-ref temp (tn-ref-next-ref ref))
613           (barf "Read is after write for temp ~S in refs of ~S."
614                 tn vop))))))
615   (values))
616
617 ;;; Check the basic sanity of the VOP linkage, then call some other
618 ;;; functions to check on the TN-Refs. We grab some info out of the VOP-Info
619 ;;; to tell us what to expect.
620 ;;;
621 ;;; [### Check that operand type restrictions are met?]
622 (defun check-ir2-block-consistency (2block)
623   (declare (type ir2-block 2block))
624   (do ((vop (ir2-block-start-vop 2block)
625             (vop-next vop))
626        (prev nil vop))
627       ((null vop)
628        (unless (eq prev (ir2-block-last-vop 2block))
629          (barf "The last VOP in ~S should be ~S." 2block prev)))
630     (unless (eq (vop-prev vop) prev)
631       (barf "PREV in ~S should be ~S." vop prev))
632
633     (unless (eq (vop-block vop) 2block)
634       (barf "BLOCK in ~S should be ~S." vop 2block))
635
636     (check-vop-refs vop)
637
638     (let* ((info (vop-info vop))
639            (atypes (template-arg-types info))
640            (rtypes (template-result-types info)))
641       (check-tn-refs (vop-args vop) vop nil
642                      (count-if-not #'(lambda (x)
643                                        (and (consp x)
644                                             (eq (car x) :constant)))
645                                    atypes)
646                      (template-more-args-type info) "args")
647       (check-tn-refs (vop-results vop) vop t
648                      (if (eq rtypes :conditional) 0 (length rtypes))
649                      (template-more-results-type info) "results")
650       (check-tn-refs (vop-temps vop) vop t 0 t "temps")
651       (unless (= (length (vop-codegen-info vop))
652                  (template-info-arg-count info))
653         (barf "wrong number of codegen info args in ~S" vop))))
654   (values))
655
656 ;;; Check stuff about the IR2 representation of Component. This assumes the
657 ;;; sanity of the basic flow graph.
658 ;;;
659 ;;; [### Also grovel global TN data structures?  Assume pack not
660 ;;; done yet?  Have separate check-tn-consistency for pre-pack and
661 ;;; check-pack-consistency for post-pack?]
662 (defun check-ir2-consistency (component)
663   (declare (type component component))
664   (do-ir2-blocks (block component)
665     (check-ir2-block-consistency block))
666   (values))
667 \f
668 ;;;; lifetime analysis checking
669
670 ;;; Dump some info about how many TNs there, and what the conflicts data
671 ;;; structures are like.
672 (defun pre-pack-tn-stats (component &optional (stream *error-output*))
673   (declare (type component component))
674   (let ((wired 0)
675         (global 0)
676         (local 0)
677         (confs 0)
678         (unused 0)
679         (const 0)
680         (temps 0)
681         (environment 0)
682         (comp 0))
683     (do-packed-tns (tn component)
684       (let ((reads (tn-reads tn))
685             (writes (tn-writes tn)))
686         (when (and reads writes
687                    (not (tn-ref-next reads)) (not (tn-ref-next writes))
688                    (eq (tn-ref-vop reads) (tn-ref-vop writes)))
689           (incf temps)))
690       (when (tn-offset tn)
691         (incf wired))
692       (unless (or (tn-reads tn) (tn-writes tn))
693         (incf unused))
694       (cond ((eq (tn-kind tn) :component)
695              (incf comp))
696             ((tn-global-conflicts tn)
697              (case (tn-kind tn)
698                ((:environment :debug-environment) (incf environment))
699                (t (incf global)))
700              (do ((conf (tn-global-conflicts tn)
701                         (global-conflicts-tn-next conf)))
702                  ((null conf))
703                (incf confs)))
704             (t
705              (incf local))))
706
707     (do ((tn (ir2-component-constant-tns (component-info component))
708              (tn-next tn)))
709         ((null tn))
710       (incf const))
711
712     (format stream
713      "~%TNs: ~D local, ~D temps, ~D constant, ~D env, ~D comp, ~D global.~@
714        Wired: ~D, Unused: ~D. ~D block~:P, ~D global conflict~:P.~%"
715        local temps const environment comp global wired unused
716        (ir2-block-count component)
717        confs))
718   (values))
719
720 ;;; If the entry in Local-TNs for TN in Block is :More, then do some checks
721 ;;; for the validity of the usage.
722 (defun check-more-tn-entry (tn block)
723   (let* ((vop (ir2-block-start-vop block))
724          (info (vop-info vop)))
725     (macrolet ((frob (more-p ops)
726                  `(and (,more-p info)
727                        (find-in #'tn-ref-across tn (,ops vop)
728                                 :key #'tn-ref-tn))))
729       (unless (and (eq vop (ir2-block-last-vop block))
730                    (or (frob template-more-args-type vop-args)
731                        (frob template-more-results-type vop-results)))
732         (barf "strange :MORE LTN entry for ~S in ~S" tn block))))
733   (values))
734
735 (defun check-tn-conflicts (component)
736   (do-packed-tns (tn component)
737     (unless (or (not (eq (tn-kind tn) :normal))
738                 (tn-reads tn)
739                 (tn-writes tn))
740       (barf "no references to ~S" tn))
741
742     (unless (tn-sc tn) (barf "~S has no SC." tn))
743
744     (let ((conf (tn-global-conflicts tn))
745           (kind (tn-kind tn)))
746       (cond
747        ((eq kind :component)
748         (unless (member tn (ir2-component-component-tns
749                             (component-info component)))
750           (barf "~S not in Component-TNs for ~S" tn component)))
751        (conf
752         (do ((conf conf (global-conflicts-tn-next conf))
753              (prev nil conf))
754             ((null conf))
755           (unless (eq (global-conflicts-tn conf) tn)
756             (barf "TN in ~S should be ~S." conf tn))
757
758           (unless (eq (global-conflicts-kind conf) :live)
759             (let* ((block (global-conflicts-block conf))
760                    (ltn (svref (ir2-block-local-tns block)
761                                (global-conflicts-number conf))))
762               (cond ((eq ltn tn))
763                     ((eq ltn :more) (check-more-tn-entry tn block))
764                     (t
765                      (barf "~S wrong in LTN map for ~S" conf tn)))))
766
767           (when prev
768             (unless (> (ir2-block-number (global-conflicts-block conf))
769                        (ir2-block-number (global-conflicts-block prev)))
770               (barf "~s and ~s out of order" prev conf)))))
771        ((member (tn-kind tn) '(:constant :specified-save)))
772        (t
773         (let ((local (tn-local tn)))
774           (unless local
775             (barf "~S has no global conflicts, but isn't local either." tn))
776           (unless (eq (svref (ir2-block-local-tns local)
777                              (tn-local-number tn))
778                       tn)
779             (barf "~S wrong in LTN map" tn))
780           (do ((ref (tn-reads tn) (tn-ref-next ref)))
781               ((null ref))
782             (unless (eq (vop-block (tn-ref-vop ref)) local)
783               (barf "~S has references in blocks other than its LOCAL block."
784                     tn)))
785           (do ((ref (tn-writes tn) (tn-ref-next ref)))
786               ((null ref))
787             (unless (eq (vop-block (tn-ref-vop ref)) local)
788               (barf "~S has references in blocks other than its LOCAL block."
789                     tn))))))))
790   (values))
791
792 (defun check-block-conflicts (component)
793   (do-ir2-blocks (block component)
794     (do ((conf (ir2-block-global-tns block)
795                (global-conflicts-next conf))
796          (prev nil conf))
797         ((null conf))
798       (when prev
799         (unless (> (tn-number (global-conflicts-tn conf))
800                    (tn-number (global-conflicts-tn prev)))
801           (barf "~S and ~S out of order in ~S" prev conf block)))
802
803       (unless (find-in #'global-conflicts-tn-next
804                        conf
805                        (tn-global-conflicts
806                         (global-conflicts-tn conf)))
807         (barf "~S missing from global conflicts of its TN" conf)))
808
809     (let ((map (ir2-block-local-tns block)))
810       (dotimes (i (ir2-block-local-tn-count block))
811         (let ((tn (svref map i)))
812           (unless (or (eq tn :more)
813                       (null tn)
814                       (tn-global-conflicts tn)
815                       (eq (tn-local tn) block))
816             (barf "strange TN ~S in LTN map for ~S" tn block)))))))
817
818 ;;; All TNs live at the beginning of an environment must be passing
819 ;;; locations associated with that environment. We make an exception for wired
820 ;;; TNs in XEP functions, since we randomly reference wired TNs to access the
821 ;;; full call passing locations.
822 (defun check-environment-lifetimes (component)
823   (dolist (fun (component-lambdas component))
824     (let* ((env (lambda-environment fun))
825            (2env (environment-info env))
826            (vars (lambda-vars fun))
827            (closure (ir2-environment-environment 2env))
828            (pc (ir2-environment-return-pc-pass 2env))
829            (fp (ir2-environment-old-fp 2env))
830            (2block (block-info
831                     (node-block
832                      (lambda-bind
833                       (environment-function env))))))
834       (do ((conf (ir2-block-global-tns 2block)
835                  (global-conflicts-next conf)))
836           ((null conf))
837         (let ((tn (global-conflicts-tn conf)))
838           (unless (or (eq (global-conflicts-kind conf) :write)
839                       (eq tn pc)
840                       (eq tn fp)
841                       (and (external-entry-point-p fun)
842                            (tn-offset tn))
843                       (member (tn-kind tn) '(:environment :debug-environment))
844                       (member tn vars :key #'leaf-info)
845                       (member tn closure :key #'cdr))
846             (barf "strange TN live at head of ~S: ~S" env tn))))))
847   (values))
848
849 ;;; Check for some basic sanity in the TN conflict data structures, and also
850 ;;; check that no TNs are unexpectedly live at environment entry.
851 (defun check-life-consistency (component)
852   (check-tn-conflicts component)
853   (check-block-conflicts component)
854   (check-environment-lifetimes component))
855 \f
856 ;;;; pack consistency checking
857
858 (defun check-pack-consistency (component)
859   (flet ((check (scs ops)
860            (do ((scs scs (cdr scs))
861                 (op ops (tn-ref-across op)))
862                ((null scs))
863              (let ((load-tn (tn-ref-load-tn op)))
864                (unless (eq (svref (car scs)
865                                   (sc-number
866                                    (tn-sc
867                                     (or load-tn (tn-ref-tn op)))))
868                            t)
869                  (barf "operand restriction not satisfied: ~S" op))))))
870     (do-ir2-blocks (block component)
871       (do ((vop (ir2-block-last-vop block) (vop-prev vop)))
872           ((null vop))
873         (let ((info (vop-info vop)))
874           (check (vop-info-result-load-scs info) (vop-results vop))
875           (check (vop-info-arg-load-scs info) (vop-args vop))))))
876   (values))
877 \f
878 ;;;; data structure dumping routines
879
880 ;;; When we print Continuations and TNs, we assign them small numeric IDs so
881 ;;; that we can get a handle on anonymous objects given a printout.
882 (macrolet ((def-frob (counter vto vfrom fto ffrom)
883              `(progn
884                 (defvar ,vto (make-hash-table :test 'eq))
885                 (defvar ,vfrom (make-hash-table :test 'eql))
886                 (proclaim '(hash-table ,vto ,vfrom))
887                 (defvar ,counter 0)
888                 (proclaim '(fixnum ,counter))
889                 
890                 (defun ,fto (x)
891                   (or (gethash x ,vto)
892                       (let ((num (incf ,counter)))
893                         (setf (gethash num ,vfrom) x)
894                         (setf (gethash x ,vto) num))))
895                 
896                 (defun ,ffrom (num)
897                   (values (gethash num ,vfrom))))))
898   (def-frob *continuation-number* *continuation-numbers* *number-continuations* cont-num num-cont)
899   (def-frob *tn-id* *tn-ids* *id-tns* tn-id id-tn)
900   (def-frob *label-id* *id-labels* *label-ids* label-id id-label))
901
902 ;;; Print out a terse one-line description of a leaf.
903 (defun print-leaf (leaf &optional (stream *standard-output*))
904   (declare (type leaf leaf) (type stream stream))
905   (etypecase leaf
906     (lambda-var (prin1 (leaf-name leaf) stream))
907     (constant (format stream "'~S" (constant-value leaf)))
908     (global-var
909      (format stream "~S {~A}" (leaf-name leaf) (global-var-kind leaf)))
910     (clambda
911       (format stream "lambda ~S ~S" (leaf-name leaf)
912               (mapcar #'leaf-name (lambda-vars leaf))))
913     (optional-dispatch
914      (format stream "optional-dispatch ~S" (leaf-name leaf)))
915     (functional
916      (assert (eq (functional-kind leaf) :top-level-xep))
917      (format stream "TL-XEP ~S"
918              (let ((info (leaf-info leaf)))
919                (etypecase info
920                  (entry-info (entry-info-name info))
921                  (byte-lambda-info :byte-compiled-entry)))))))
922
923 ;;; Attempt to find a block given some thing that has to do with it.
924 (declaim (ftype (function (t) cblock) block-or-lose))
925 (defun block-or-lose (thing)
926   (ctypecase thing
927     (cblock thing)
928     (ir2-block (ir2-block-block thing))
929     (vop (block-or-lose (vop-block thing)))
930     (tn-ref (block-or-lose (tn-ref-vop thing)))
931     (continuation (continuation-block thing))
932     (node (node-block thing))
933     (component (component-head thing))
934 #|    (cloop (loop-head thing))|#
935     (integer (continuation-block (num-cont thing)))
936     (functional (node-block (lambda-bind (main-entry thing))))
937     (null (error "Bad thing: ~S." thing))
938     (symbol (block-or-lose (gethash thing *free-functions*)))))
939
940 ;;; Print cN.
941 (defun print-continuation (cont)
942   (declare (type continuation cont))
943   (format t " c~D" (cont-num cont))
944   (values))
945
946 ;;; Print out the nodes in Block in a format oriented toward representing
947 ;;; what the code does.
948 (defun print-nodes (block)
949   (setq block (block-or-lose block))
950   (format t "~%block start c~D" (cont-num (block-start block)))
951
952   (let ((last (block-last block)))
953     (terpri)
954     (do ((cont (block-start block) (node-cont (continuation-next cont))))
955         (())
956       (let ((node (continuation-next cont)))
957         (format t "~3D: " (cont-num (node-cont node)))
958         (etypecase node
959           (ref (print-leaf (ref-leaf node)))
960           (basic-combination
961            (let ((kind (basic-combination-kind node)))
962              (format t "~(~A ~A~) c~D"
963                      (if (function-info-p kind) "known" kind)
964                      (type-of node)
965                      (cont-num (basic-combination-fun node)))
966              (dolist (arg (basic-combination-args node))
967                (if arg
968                    (print-continuation arg)
969                    (format t " <none>")))))
970           (cset
971            (write-string "set ")
972            (print-leaf (set-var node))
973            (print-continuation (set-value node)))
974           (cif
975            (format t "if c~D" (cont-num (if-test node)))
976            (print-continuation (block-start (if-consequent node)))
977            (print-continuation (block-start (if-alternative node))))
978           (bind
979            (write-string "bind ")
980            (print-leaf (bind-lambda node)))
981           (creturn
982            (format t "return c~D " (cont-num (return-result node)))
983            (print-leaf (return-lambda node)))
984           (entry
985            (format t "entry ~S" (entry-exits node)))
986           (exit
987            (let ((value (exit-value node)))
988              (cond (value
989                     (format t "exit c~D" (cont-num value)))
990                    ((exit-entry node)
991                     (format t "exit <no value>"))
992                    (t
993                     (format t "exit <degenerate>"))))))
994         (terpri)
995         (when (eq node last) (return)))))
996
997   (let ((succ (block-succ block)))
998     (format t "successors~{ c~D~}~%"
999             (mapcar #'(lambda (x) (cont-num (block-start x))) succ)))
1000   (values))
1001
1002 ;;; Print a useful representation of a TN. If the TN has a leaf, then do a
1003 ;;; Print-Leaf on that, otherwise print a generated ID.
1004 (defun print-tn (tn &optional (stream *standard-output*))
1005   (declare (type tn tn))
1006   (let ((leaf (tn-leaf tn)))
1007     (cond (leaf
1008            (print-leaf leaf stream)
1009            (format stream "!~D" (tn-id tn)))
1010           (t
1011            (format stream "t~D" (tn-id tn))))
1012     (when (and (tn-sc tn) (tn-offset tn))
1013       (format stream "[~A]" (location-print-name tn)))))
1014
1015 ;;; Print the TN-Refs representing some operands to a VOP, linked by
1016 ;;; TN-Ref-Across.
1017 (defun print-operands (refs)
1018   (declare (type (or tn-ref null) refs))
1019   (pprint-logical-block (*standard-output* nil)
1020     (do ((ref refs (tn-ref-across ref)))
1021         ((null ref))
1022       (let ((tn (tn-ref-tn ref))
1023             (ltn (tn-ref-load-tn ref)))
1024         (cond ((not ltn)
1025                (print-tn tn))
1026               (t
1027                (print-tn tn)
1028                (princ (if (tn-ref-write-p ref) #\< #\>))
1029                (print-tn ltn)))
1030         (princ #\space)
1031         (pprint-newline :fill)))))
1032
1033 ;;; Print the vop, putting args, info and results on separate lines, if
1034 ;;; necessary.
1035 (defun print-vop (vop)
1036   (pprint-logical-block (*standard-output* nil)
1037     (princ (vop-info-name (vop-info vop)))
1038     (princ #\space)
1039     (pprint-indent :current 0)
1040     (print-operands (vop-args vop))
1041     (pprint-newline :linear)
1042     (when (vop-codegen-info vop)
1043       (princ (with-output-to-string (stream)
1044                (let ((*print-level* 1)
1045                      (*print-length* 3))
1046                  (format stream "{~{~S~^ ~}} " (vop-codegen-info vop)))))
1047       (pprint-newline :linear))
1048     (when (vop-results vop)
1049       (princ "=> ")
1050       (print-operands (vop-results vop))))
1051   (terpri))
1052
1053 ;;; Print the VOPs in the specified IR2 block.
1054 (defun print-ir2-block (block)
1055   (declare (type ir2-block block))
1056   (cond
1057    ((eq (block-info (ir2-block-block block)) block)
1058     (format t "~%IR2 block start c~D~%"
1059             (cont-num (block-start (ir2-block-block block))))
1060     (let ((label (ir2-block-%label block)))
1061       (when label
1062         (format t "L~D:~%" (label-id label)))))
1063    (t
1064     (format t "<overflow>~%")))
1065
1066   (do ((vop (ir2-block-start-vop block)
1067             (vop-next vop))
1068        (number 0 (1+ number)))
1069       ((null vop))
1070     (format t "~D: " number)
1071     (print-vop vop)))
1072
1073 ;;; Like Print-Nodes, but dumps the IR2 representation of the code in Block.
1074 (defun print-vops (block)
1075   (setq block (block-or-lose block))
1076   (let ((2block (block-info block)))
1077     (print-ir2-block 2block)
1078     (do ((b (ir2-block-next 2block) (ir2-block-next b)))
1079         ((not (eq (ir2-block-block b) block)))
1080       (print-ir2-block b)))
1081   (values))
1082
1083 ;;; Scan the IR2 blocks in emission order.
1084 (defun print-ir2-blocks (thing)
1085   (do-ir2-blocks (block (block-component (block-or-lose thing)))
1086     (print-ir2-block block))
1087   (values))
1088
1089 ;;; Do a Print-Nodes on Block and all blocks reachable from it by successor
1090 ;;; links.
1091 (defun print-blocks (block)
1092   (setq block (block-or-lose block))
1093   (do-blocks (block (block-component block) :both)
1094     (setf (block-flag block) nil))
1095   (labels ((walk (block)
1096              (unless (block-flag block)
1097                (setf (block-flag block) t)
1098                (when (block-start block)
1099                  (print-nodes block))
1100                (dolist (block (block-succ block))
1101                  (walk block)))))
1102     (walk block))
1103   (values))
1104
1105 ;;; Print all blocks in Block's component in DFO.
1106 (defun print-all-blocks (thing)
1107   (do-blocks (block (block-component (block-or-lose thing)))
1108     (handler-case (print-nodes block)
1109       (error (condition)
1110         (format t "~&~A...~%" condition))))
1111   (values))
1112
1113 (defvar *list-conflicts-table* (make-hash-table :test 'eq))
1114
1115 ;;; Add all Always-Live TNs in Block to the conflicts. TN is ignored when
1116 ;;; it appears in the global conflicts.
1117 (defun add-always-live-tns (block tn)
1118   (declare (type ir2-block block) (type tn tn))
1119   (do ((conf (ir2-block-global-tns block)
1120              (global-conflicts-next conf)))
1121       ((null conf))
1122     (when (eq (global-conflicts-kind conf) :live)
1123       (let ((btn (global-conflicts-tn conf)))
1124         (unless (eq btn tn)
1125           (setf (gethash btn *list-conflicts-table*) t)))))
1126   (values))
1127
1128 ;;; Add all local TNs in block to the conflicts.
1129 (defun add-all-local-tns (block)
1130   (declare (type ir2-block block))
1131   (let ((ltns (ir2-block-local-tns block)))
1132     (dotimes (i (ir2-block-local-tn-count block))
1133       (setf (gethash (svref ltns i) *list-conflicts-table*) t)))
1134   (values))
1135
1136 ;;; Make a list out of all of the recorded conflicts.
1137 (defun listify-conflicts-table ()
1138   (collect ((res))
1139     (maphash #'(lambda (k v)
1140                  (declare (ignore v))
1141                  (when k
1142                    (res k)))
1143              *list-conflicts-table*)
1144     (clrhash *list-conflicts-table*)
1145     (res)))
1146
1147 (defun list-conflicts (tn)
1148   #!+sb-doc
1149   "Return a list of a the TNs that conflict with TN. Sort of, kind of. For
1150   debugging use only. Probably doesn't work on :COMPONENT TNs."
1151   (assert (member (tn-kind tn) '(:normal :environment :debug-environment)))
1152   (let ((confs (tn-global-conflicts tn)))
1153     (cond (confs
1154            (clrhash *list-conflicts-table*)
1155            (do ((conf confs (global-conflicts-tn-next conf)))
1156                ((null conf))
1157              (let ((block (global-conflicts-block conf)))
1158                (add-always-live-tns block tn)
1159                (if (eq (global-conflicts-kind conf) :live)
1160                    (add-all-local-tns block)
1161                    (let ((bconf (global-conflicts-conflicts conf))
1162                          (ltns (ir2-block-local-tns block)))
1163                      (dotimes (i (ir2-block-local-tn-count block))
1164                        (when (/= (sbit bconf i) 0)
1165                          (setf (gethash (svref ltns i) *list-conflicts-table*)
1166                                t)))))))
1167            (listify-conflicts-table))
1168           (t
1169            (let* ((block (tn-local tn))
1170                   (ltns (ir2-block-local-tns block))
1171                   (confs (tn-local-conflicts tn)))
1172              (collect ((res))
1173                (dotimes (i (ir2-block-local-tn-count block))
1174                  (when (/= (sbit confs i) 0)
1175                    (let ((tn (svref ltns i)))
1176                      (when (and tn (not (eq tn :more))
1177                                 (not (tn-global-conflicts tn)))
1178                        (res tn)))))
1179                (do ((gtn (ir2-block-global-tns block)
1180                          (global-conflicts-next gtn)))
1181                    ((null gtn))
1182                  (when (or (eq (global-conflicts-kind gtn) :live)
1183                            (/= (sbit confs (global-conflicts-number gtn)) 0))
1184                    (res (global-conflicts-tn gtn))))
1185                (res)))))))
1186
1187 (defun nth-vop (thing n)
1188   #!+sb-doc
1189   "Return the Nth VOP in the IR2-Block pointed to by Thing."
1190   (let ((block (block-info (block-or-lose thing))))
1191     (do ((i 0 (1+ i))
1192          (vop (ir2-block-start-vop block) (vop-next vop)))
1193         ((= i n) vop))))