1 ;;;; stuff that creates debugger information from the compiler's
2 ;;;; internal data structures
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.
15 (deftype byte-buffer () '(vector (unsigned-byte 8)))
16 (defvar *byte-buffer*)
17 (declaim (type byte-buffer *byte-buffer*))
21 (deftype location-kind ()
22 '(member :unknown-return :known-return :internal-error :non-local-exit
23 :block-start :call-site :single-value-return :non-local-entry
26 ;;; The LOCATION-INFO structure holds the information what we need
27 ;;; about locations which code generation decided were "interesting".
28 (defstruct (location-info
29 (:constructor make-location-info (kind label vop))
31 ;; The kind of location noted.
32 (kind nil :type location-kind)
33 ;; The label pointing to the interesting code location.
34 (label nil :type (or label index null))
35 ;; The VOP that emitted this location (for node, save-set, ir2-block, etc.)
38 ;;; This is called during code generation in places where there is an
39 ;;; "interesting" location: someplace where we are likely to end up
40 ;;; in the debugger, and thus want debug info.
41 (defun note-debug-location (vop label kind)
42 (declare (type vop vop) (type (or label null) label)
43 (type location-kind kind))
44 (let ((location (make-location-info kind label vop)))
45 (setf (ir2-block-locations (vop-block vop))
46 (nconc (ir2-block-locations (vop-block vop))
50 #!-sb-fluid (declaim (inline ir2-block-physenv))
51 (defun ir2-block-physenv (2block)
52 (declare (type ir2-block 2block))
53 (block-physenv (ir2-block-block 2block)))
55 ;;; Given a local conflicts vector and an IR2 block to represent the
56 ;;; set of live TNs, and the VAR-LOCS hash-table representing the
57 ;;; variables dumped, compute a bit-vector representing the set of
58 ;;; live variables. If the TN is environment-live, we only mark it as
59 ;;; live when it is in scope at NODE.
60 (defun compute-live-vars (live node block var-locs vop)
61 (declare (type ir2-block block) (type local-tn-bit-vector live)
62 (type hash-table var-locs) (type node node)
63 (type (or vop null) vop))
64 (let ((res (make-array (logandc2 (+ (hash-table-count var-locs) 7) 7)
68 (ir2-component-spilled-vops
69 (component-info *component-being-compiled*)))))
70 (do-live-tns (tn live block)
71 (let ((leaf (tn-leaf tn)))
72 (when (and (lambda-var-p leaf)
73 (or (not (member (tn-kind tn)
74 '(:environment :debug-environment)))
75 (rassoc leaf (lexenv-vars (node-lexenv node))))
77 (not (member tn spilled))))
78 (let ((num (gethash leaf var-locs)))
80 (setf (sbit res num) 1))))))
83 ;;; The PC for the location most recently dumped.
84 (defvar *previous-location*)
85 (declaim (type index *previous-location*))
87 ;;; Dump a compiled debug-location into *BYTE-BUFFER* that describes
88 ;;; the code/source map and live info. If true, VOP is the VOP
89 ;;; associated with this location, for use in determining whether TNs
91 (defun dump-1-location (node block kind tlf-num label live var-locs vop)
92 (declare (type node node) (type ir2-block block)
93 (type (or null local-tn-bit-vector) live)
94 (type (or label index) label)
95 (type location-kind kind) (type (or index null) tlf-num)
96 (type hash-table var-locs) (type (or vop null) vop))
99 (dpb (position-or-lose kind *compiled-code-location-kinds*)
100 compiled-code-location-kind-byte
104 (let ((loc (if (fixnump label) label (label-position label))))
105 (write-var-integer (- loc *previous-location*) *byte-buffer*)
106 (setq *previous-location* loc))
108 (let ((path (node-source-path node)))
110 (write-var-integer (source-path-tlf-number path) *byte-buffer*))
111 (write-var-integer (source-path-form-number path) *byte-buffer*))
114 (write-packed-bit-vector (compute-live-vars live node block var-locs vop)
116 (write-packed-bit-vector
117 (make-array (logandc2 (+ (hash-table-count var-locs) 7) 7)
122 (write-var-string (or (and (typep node 'combination)
123 (combination-step-info node))
128 ;;; Extract context info from a Location-Info structure and use it to
129 ;;; dump a compiled code-location.
130 (defun dump-location-from-info (loc tlf-num var-locs)
131 (declare (type location-info loc) (type (or index null) tlf-num)
132 (type hash-table var-locs))
133 (let ((vop (location-info-vop loc)))
134 (dump-1-location (vop-node vop)
136 (location-info-kind loc)
138 (location-info-label loc)
144 ;;; Scan all the blocks, determining if all locations are in the same
145 ;;; TLF, and returning it or NIL.
146 (defun find-tlf-number (fun)
147 (declare (type clambda fun))
148 (let ((res (source-path-tlf-number (node-source-path (lambda-bind fun)))))
149 (declare (type (or index null) res))
150 (do-physenv-ir2-blocks (2block (lambda-physenv fun))
151 (let ((block (ir2-block-block 2block)))
152 (when (eq (block-info block) 2block)
153 (unless (eql (source-path-tlf-number
155 (block-start-node block)))
159 (dolist (loc (ir2-block-locations 2block))
160 (unless (eql (source-path-tlf-number
162 (vop-node (location-info-vop loc))))
167 ;;; Dump out the number of locations and the locations for Block.
168 (defun dump-block-locations (block locations tlf-num var-locs)
169 (declare (type cblock block) (list locations))
171 (eq (location-info-kind (first locations))
173 (write-var-integer (length locations) *byte-buffer*)
174 (let ((2block (block-info block)))
175 (write-var-integer (+ (length locations) 1) *byte-buffer*)
176 (dump-1-location (block-start-node block)
177 2block :block-start tlf-num
178 (ir2-block-%label 2block)
179 (ir2-block-live-out 2block)
182 (dolist (loc locations)
183 (dump-location-from-info loc tlf-num var-locs))
186 ;;; Dump the successors of Block, being careful not to fly into space
187 ;;; on weird successors.
188 (defun dump-block-successors (block physenv)
189 (declare (type cblock block) (type physenv physenv))
190 (let* ((tail (component-tail (block-component block)))
191 (succ (block-succ block))
194 (or (eq (car succ) tail)
195 (not (eq (block-physenv (car succ)) physenv))))
199 (dpb (length valid-succ) compiled-debug-block-nsucc-byte 0)
201 (let ((base (block-number
203 (lambda-bind (physenv-lambda physenv))))))
204 (dolist (b valid-succ)
206 (the index (- (block-number b) base))
210 ;;; Return a vector and an integer (or null) suitable for use as the
211 ;;; BLOCKS and TLF-NUMBER in FUN's DEBUG-FUN. This requires two
212 ;;; passes to compute:
213 ;;; -- Scan all blocks, dumping the header and successors followed
214 ;;; by all the non-elsewhere locations.
215 ;;; -- Dump the elsewhere block header and all the elsewhere
216 ;;; locations (if any.)
217 (defun compute-debug-blocks (fun var-locs)
218 (declare (type clambda fun) (type hash-table var-locs))
219 (setf (fill-pointer *byte-buffer*) 0)
220 (let ((*previous-location* 0)
221 (tlf-num (find-tlf-number fun))
222 (physenv (lambda-physenv fun))
225 (collect ((elsewhere))
226 (do-physenv-ir2-blocks (2block physenv)
227 (let ((block (ir2-block-block 2block)))
228 (when (eq (block-info block) 2block)
230 (dump-block-locations prev-block prev-locs tlf-num var-locs))
231 (setq prev-block block prev-locs ())
232 (dump-block-successors block physenv)))
234 (collect ((here prev-locs))
235 (dolist (loc (ir2-block-locations 2block))
236 (if (label-elsewhere-p (location-info-label loc))
239 (setq prev-locs (here))))
241 (dump-block-locations prev-block prev-locs tlf-num var-locs)
244 (vector-push-extend compiled-debug-block-elsewhere-p *byte-buffer*)
245 (write-var-integer (length (elsewhere)) *byte-buffer*)
246 (dolist (loc (elsewhere))
247 (dump-location-from-info loc tlf-num var-locs))))
249 (values (copy-seq *byte-buffer*) tlf-num)))
251 ;;; Return DEBUG-SOURCE structure containing information derived from
253 (defun debug-source-for-info (info &key function)
254 (declare (type source-info info))
255 (let ((file-info (get-toplevelish-file-info info)))
257 :compiled (source-info-start-time info)
259 :namestring (or *source-namestring*
260 (make-file-info-namestring
261 (if (pathnamep (file-info-name file-info))
262 (file-info-name file-info))
264 :created (file-info-write-date file-info)
265 :source-root (file-info-source-root file-info)
266 :start-positions (coerce-to-smallest-eltype
267 (file-info-positions file-info))
269 :form (let ((direct-file-info (source-info-file-info info)))
270 (when (eq :lisp (file-info-name direct-file-info))
271 (let ((form (elt (file-info-forms direct-file-info) 0)))
272 ;; The form COMPILE saves may include gunk
273 ;; from %SIMPLE-EVAL -- this gets rid of that.
274 (sb!impl::eval-lambda-source-lambda form))))
275 :function function)))
277 ;;; Given an arbitrary sequence, coerce it to an unsigned vector if
278 ;;; possible. Ordinarily we coerce it to the smallest specialized
279 ;;; vector we can. However, we also have a special hack for
280 ;;; cross-compiling at bootstrap time, when arbitrarily-specialized
281 ;;; vectors aren't fully supported: in that case, we coerce it only to
282 ;;; a vector whose element size is an integer multiple of output byte
284 (defun coerce-to-smallest-eltype (seq)
287 (if (typep x 'unsigned-byte)
290 (return-from coerce-to-smallest-eltype
291 (coerce seq 'simple-vector)))))
297 (let ((specializer `(unsigned-byte
299 ((unsigned-byte 8) 8)
300 ((unsigned-byte 16) 16)
301 ((unsigned-byte 32) 32)))))
302 ;; cross-compilers beware! It would be possible for the
303 ;; upgraded-array-element-type of (UNSIGNED-BYTE 16) to be
304 ;; (SIGNED-BYTE 17) or (UNSIGNED-BYTE 23), and this is
305 ;; completely valid by ANSI. However, the cross-compiler
306 ;; doesn't know how to dump (in practice) anything but the
307 ;; above three specialized array types, so make it break here
308 ;; if this is violated.
311 ;; not SB!XC:UPGRADED-ARRAY-ELEMENT-TYPE, because we are
312 ;; worried about whether the host's implementation of arrays.
313 (let ((uaet (upgraded-array-element-type specializer)))
314 (dolist (et '((unsigned-byte 8)
318 (when (and (subtypep et uaet) (subtypep uaet et))
320 (coerce seq `(simple-array ,specializer (*)))))))
324 ;;; Return a SC-OFFSET describing TN's location.
325 (defun tn-sc-offset (tn)
326 (declare (type tn tn))
327 (make-sc-offset (sc-number (tn-sc tn))
330 (defun lambda-ancestor-p (maybe-ancestor maybe-descendant)
331 (declare (type clambda maybe-ancestor)
332 (type (or clambda null) maybe-descendant))
334 (when (eq maybe-ancestor maybe-descendant)
336 (setf maybe-descendant (lambda-parent maybe-descendant))
337 (when (null maybe-descendant)
340 ;;; Dump info to represent VAR's location being TN. ID is an integer
341 ;;; that makes VAR's name unique in the function. BUFFER is the vector
342 ;;; we stick the result in. If MINIMAL, we suppress name dumping, and
343 ;;; set the minimal flag.
345 ;;; The DEBUG-VAR is only marked as always-live if the TN is
346 ;;; environment live and is an argument. If a :DEBUG-ENVIRONMENT TN,
347 ;;; then we also exclude set variables, since the variable is not
348 ;;; guaranteed to be live everywhere in that case.
349 (defun dump-1-var (fun var tn id minimal buffer)
350 (declare (type lambda-var var) (type (or tn null) tn) (type index id)
352 (let* ((name (leaf-debug-name var))
353 (save-tn (and tn (tn-save-tn tn)))
354 (kind (and tn (tn-kind tn)))
356 (declare (type index flags))
358 (setq flags (logior flags compiled-debug-var-minimal-p))
359 (unless (and tn (tn-offset tn))
360 (setq flags (logior flags compiled-debug-var-deleted-p))))
361 (when (and (or (eq kind :environment)
362 (and (eq kind :debug-environment)
363 (null (basic-var-sets var))))
364 (not (gethash tn (ir2-component-spilled-tns
365 (component-info *component-being-compiled*))))
366 (lambda-ancestor-p (lambda-var-home var) fun))
367 (setq flags (logior flags compiled-debug-var-environment-live)))
369 (setq flags (logior flags compiled-debug-var-save-loc-p)))
370 (unless (or (zerop id) minimal)
371 (setq flags (logior flags compiled-debug-var-id-p)))
372 (vector-push-extend flags buffer)
374 (vector-push-extend name buffer)
376 (vector-push-extend id buffer)))
377 (if (and tn (tn-offset tn))
378 (vector-push-extend (tn-sc-offset tn) buffer)
381 (vector-push-extend (tn-sc-offset save-tn) buffer)))
384 ;;; Return a vector suitable for use as the DEBUG-FUN-VARS
385 ;;; of FUN. LEVEL is the current DEBUG-INFO quality. VAR-LOCS is a
386 ;;; hash table in which we enter the translation from LAMBDA-VARS to
387 ;;; the relative position of that variable's location in the resulting
389 (defun compute-vars (fun level var-locs)
390 (declare (type clambda fun) (type hash-table var-locs))
392 (labels ((frob-leaf (leaf tn gensym-p)
393 (let ((name (leaf-debug-name leaf)))
394 (when (and name (leaf-refs leaf) (tn-offset tn)
395 (or gensym-p (symbol-package name)))
396 (vars (cons leaf tn)))))
397 (frob-lambda (x gensym-p)
398 (dolist (leaf (lambda-vars x))
399 (frob-leaf leaf (leaf-info leaf) gensym-p))))
402 (dolist (x (ir2-physenv-closure (physenv-info (lambda-physenv fun))))
403 (let ((thing (car x)))
404 (when (lambda-var-p thing)
405 (frob-leaf thing (cdr x) (= level 3)))))
407 (dolist (let (lambda-lets fun))
408 (frob-lambda let (= level 3)))))
410 (let ((sorted (sort (vars) #'string<
412 (symbol-name (leaf-debug-name (car x))))))
416 (buffer (make-array 0 :fill-pointer 0 :adjustable t)))
417 (declare (type (or simple-string null) prev-name)
421 (name (symbol-name (leaf-debug-name var))))
422 (cond ((and prev-name (string= prev-name name))
425 (setq id 0 prev-name name)))
426 (dump-1-var fun var (cdr x) id nil buffer)
427 (setf (gethash var var-locs) i)
429 (coerce buffer 'simple-vector))))
431 ;;; Return a vector suitable for use as the DEBUG-FUN-VARS of
432 ;;; FUN, representing the arguments to FUN in minimal variable format.
433 (defun compute-minimal-vars (fun)
434 (declare (type clambda fun))
435 (let ((buffer (make-array 0 :fill-pointer 0 :adjustable t)))
436 (dolist (var (lambda-vars fun))
437 (dump-1-var fun var (leaf-info var) 0 t buffer))
438 (coerce buffer 'simple-vector)))
440 ;;; Return VAR's relative position in the function's variables (determined
441 ;;; from the VAR-LOCS hashtable). If VAR is deleted, then return DELETED.
442 (defun debug-location-for (var var-locs)
443 (declare (type lambda-var var) (type hash-table var-locs))
444 (let ((res (gethash var var-locs)))
447 (aver (or (null (leaf-refs var))
448 (not (tn-offset (leaf-info var)))))
451 ;;;; arguments/returns
453 ;;; Return a vector to be used as the COMPILED-DEBUG-FUN-ARGS for FUN.
454 ;;; If FUN is the MAIN-ENTRY for an optional dispatch, then look at
455 ;;; the ARGLIST to determine the syntax, otherwise pretend all
456 ;;; arguments are fixed.
458 ;;; ### This assumption breaks down in EPs other than the main-entry,
459 ;;; since they may or may not have supplied-p vars, etc.
460 (defun compute-args (fun var-locs)
461 (declare (type clambda fun) (type hash-table var-locs))
463 (let ((od (lambda-optional-dispatch fun)))
464 (if (and od (eq (optional-dispatch-main-entry od) fun))
465 (let ((actual-vars (lambda-vars fun))
467 (labels ((one-arg (arg)
468 (let ((info (lambda-var-arg-info arg))
469 (actual (pop actual-vars)))
471 (case (arg-info-kind info)
473 (res (arg-info-key info)))
475 (let ((more (arg-info-default info)))
476 (cond ((and (consp more) (third more))
477 (one-arg (first (arg-info-default info)))
478 (one-arg (second (arg-info-default info)))
479 (return-from one-arg))
481 (setf (arg-info-default info) t)))
488 (setq saw-optional t))))
489 (res (debug-location-for actual var-locs))
490 (when (arg-info-supplied-p info)
492 (res (debug-location-for (pop actual-vars) var-locs))))
494 (res (debug-location-for actual var-locs)))))))
495 (dolist (arg (optional-dispatch-arglist od))
497 (dolist (var (lambda-vars fun))
498 (res (debug-location-for var var-locs)))))
500 (coerce-to-smallest-eltype (res))))
502 ;;; Return a vector of SC offsets describing FUN's return locations.
503 ;;; (Must be known values return...)
504 (defun compute-debug-returns (fun)
505 (coerce-to-smallest-eltype
506 (mapcar (lambda (loc)
508 (return-info-locations (tail-set-info (lambda-tail-set fun))))))
512 ;;; Return a C-D-F structure with all the mandatory slots filled in.
513 (defun dfun-from-fun (fun)
514 (declare (type clambda fun))
515 (let* ((2env (physenv-info (lambda-physenv fun)))
516 (dispatch (lambda-optional-dispatch fun))
517 (main-p (and dispatch
518 (eq fun (optional-dispatch-main-entry dispatch)))))
519 (make-compiled-debug-fun
520 :name (leaf-debug-name fun)
521 :kind (if main-p nil (functional-kind fun))
522 :return-pc (tn-sc-offset (ir2-physenv-return-pc 2env))
523 :old-fp (tn-sc-offset (ir2-physenv-old-fp 2env))
524 :start-pc (label-position (ir2-physenv-environment-start 2env))
525 :elsewhere-pc (label-position (ir2-physenv-elsewhere-start 2env)))))
527 ;;; Return a complete C-D-F structure for FUN. This involves
528 ;;; determining the DEBUG-INFO level and filling in optional slots as
530 (defun compute-1-debug-fun (fun var-locs)
531 (declare (type clambda fun) (type hash-table var-locs))
532 (let* ((dfun (dfun-from-fun fun))
533 (actual-level (policy (lambda-bind fun) compute-debug-fun))
534 (level (if #!+sb-dyncount *collect-dynamic-statistics*
538 (cond ((zerop level))
540 (let ((od (lambda-optional-dispatch fun)))
542 (not (eq (optional-dispatch-main-entry od) fun)))))
543 (setf (compiled-debug-fun-vars dfun)
544 (compute-minimal-vars fun))
545 (setf (compiled-debug-fun-arguments dfun) :minimal))
547 (setf (compiled-debug-fun-vars dfun)
548 (compute-vars fun level var-locs))
549 (setf (compiled-debug-fun-arguments dfun)
550 (compute-args fun var-locs))))
553 (multiple-value-bind (blocks tlf-num)
554 (compute-debug-blocks fun var-locs)
555 (setf (compiled-debug-fun-tlf-number dfun) tlf-num)
556 (setf (compiled-debug-fun-blocks dfun) blocks))
557 (setf (compiled-debug-fun-tlf-number dfun) (find-tlf-number fun)))
560 (setf (compiled-debug-fun-returns dfun) :standard)
561 (let ((info (tail-set-info (lambda-tail-set fun))))
563 (cond ((eq (return-info-kind info) :unknown)
564 (setf (compiled-debug-fun-returns dfun)
567 (setf (compiled-debug-fun-returns dfun)
568 (compute-debug-returns fun)))))))
571 ;;;; full component dumping
573 ;;; Compute the full form (simple-vector) function map.
574 (defun compute-debug-fun-map (sorted)
575 (declare (list sorted))
576 (let* ((len (1- (* (length sorted) 2)))
577 (funs-vec (make-array len)))
579 (sorted sorted (cdr sorted)))
582 (let ((dfun (car sorted)))
584 (setf (svref funs-vec i) (car dfun)))
585 (setf (svref funs-vec (1+ i)) (cdr dfun))))
588 ;;; Return a DEBUG-INFO structure describing COMPONENT. This has to be
589 ;;; called after assembly so that source map information is available.
590 (defun debug-info-for-component (component)
591 (declare (type component component))
593 (var-locs (make-hash-table :test 'eq))
594 (*byte-buffer* (make-array 10
595 :element-type '(unsigned-byte 8)
598 (dolist (lambda (component-lambdas component))
600 (push (cons (label-position (block-label (lambda-block lambda)))
601 (compute-1-debug-fun lambda var-locs))
603 (let* ((sorted (sort dfuns #'< :key #'car))
604 (fun-map (compute-debug-fun-map sorted)))
605 (make-compiled-debug-info :name (component-name component)
608 ;;; Write BITS out to BYTE-BUFFER in backend byte order. The length of
609 ;;; BITS must be evenly divisible by eight.
610 (defun write-packed-bit-vector (bits byte-buffer)
611 (declare (type simple-bit-vector bits) (type byte-buffer byte-buffer))
613 ;; Enforce constraint from CMU-CL-era comment.
614 (aver (zerop (mod (length bits) 8)))
616 (multiple-value-bind (initial step done)
617 (ecase *backend-byte-order*
618 (:little-endian (values 0 1 8))
619 (:big-endian (values 7 -1 -1)))
620 (let ((shift initial)
622 (dotimes (i (length bits))
623 (let ((int (aref bits i)))
624 (setf byte (logior byte (ash int shift)))
627 (vector-push-extend byte byte-buffer)
630 (unless (= shift initial)
631 (vector-push-extend byte byte-buffer))))