1 ;;;; disassembler-related stuff not needed in cross-compilation host
3 ;;;; This software is part of the SBCL system. See the README file for
6 ;;;; This software is derived from the CMU CL system, which was
7 ;;;; written at Carnegie Mellon University and released into the
8 ;;;; public domain. The software is in the public domain and is
9 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
10 ;;;; files for more information.
12 (in-package "SB!DISASSEM")
14 ;;;; FIXME: A lot of stupid package prefixes would go away if DISASSEM
15 ;;;; would use the SB!DI package. And some more would go away if it would
16 ;;;; use SB!SYS (in order to get to the SAP-FOO operators).
18 ;;;; combining instructions where one specializes another
20 ;;; Return non-NIL if the instruction SPECIAL is a more specific
21 ;;; version of GENERAL (i.e., the same instruction, but with more
23 (defun inst-specializes-p (special general)
24 (declare (type instruction special general))
25 (let ((smask (inst-mask special))
26 (gmask (inst-mask general)))
27 (and (dchunk= (inst-id general)
28 (dchunk-and (inst-id special) gmask))
29 (dchunk-strict-superset-p smask gmask))))
31 ;;; a bit arbitrary, but should work ok...
33 ;;; Return an integer corresponding to the specificity of the
35 (defun specializer-rank (inst)
36 (declare (type instruction inst))
37 (* (dchunk-count-bits (inst-mask inst)) 4))
39 ;;; Order the list of instructions INSTS with more specific (more
40 ;;; constant bits, or same-as argument constains) ones first. Returns
42 (defun order-specializers (insts)
43 (declare (type list insts))
44 (sort insts #'> :key #'specializer-rank))
46 (defun specialization-error (insts)
48 "~@<Instructions either aren't related or conflict in some way: ~4I~_~S~:>"
51 ;;; Given a list of instructions INSTS, Sees if one of these instructions is a
52 ;;; more general form of all the others, in which case they are put into its
53 ;;; specializers list, and it is returned. Otherwise an error is signaled.
54 (defun try-specializing (insts)
55 (declare (type list insts))
56 (let ((masters (copy-list insts)))
57 (dolist (possible-master insts)
58 (dolist (possible-specializer insts)
59 (unless (or (eq possible-specializer possible-master)
60 (inst-specializes-p possible-specializer possible-master))
61 (setf masters (delete possible-master masters))
62 (return) ; exit the inner loop
65 (specialization-error insts))
67 (error "multiple specializing masters: ~S" masters))
69 (let ((master (car masters)))
70 (setf (inst-specializers master)
71 (order-specializers (remove master insts)))
74 ;;;; choosing an instruction
76 #!-sb-fluid (declaim (inline inst-matches-p choose-inst-specialization))
78 ;;; Return non-NIL if all constant-bits in INST match CHUNK.
79 (defun inst-matches-p (inst chunk)
80 (declare (type instruction inst)
82 (dchunk= (dchunk-and (inst-mask inst) chunk) (inst-id inst)))
84 ;;; Given an instruction object, INST, and a bit-pattern, CHUNK, pick
85 ;;; the most specific instruction on INST's specializer list whose
86 ;;; constraints are met by CHUNK. If none do, then return INST.
87 (defun choose-inst-specialization (inst chunk)
88 (declare (type instruction inst)
90 (or (dolist (spec (inst-specializers inst) nil)
91 (declare (type instruction spec))
92 (when (inst-matches-p spec chunk)
96 ;;;; searching for an instruction in instruction space
98 ;;; Return the instruction object within INST-SPACE corresponding to the
99 ;;; bit-pattern CHUNK, or NIL if there isn't one.
100 (defun find-inst (chunk inst-space)
101 (declare (type dchunk chunk)
102 (type (or null inst-space instruction) inst-space))
103 (etypecase inst-space
106 (if (inst-matches-p inst-space chunk)
107 (choose-inst-specialization inst-space chunk)
110 (let* ((mask (ispace-valid-mask inst-space))
111 (id (dchunk-and mask chunk)))
112 (declare (type dchunk id mask))
113 (dolist (choice (ispace-choices inst-space))
114 (declare (type inst-space-choice choice))
115 (when (dchunk= id (ischoice-common-id choice))
116 (return (find-inst chunk (ischoice-subspace choice)))))))))
118 ;;;; building the instruction space
120 ;;; Returns an instruction-space object corresponding to the list of
121 ;;; instructions INSTS. If the optional parameter INITIAL-MASK is
122 ;;; supplied, only bits it has set are used.
123 (defun build-inst-space (insts &optional (initial-mask dchunk-one))
124 ;; This is done by finding any set of bits that's common to
125 ;; all instructions, building an instruction-space node that selects on those
126 ;; bits, and recursively handle sets of instructions with a common value for
127 ;; these bits (which, since there should be fewer instructions than in INSTS,
128 ;; should have some additional set of bits to select on, etc). If there
129 ;; are no common bits, or all instructions have the same value within those
130 ;; bits, TRY-SPECIALIZING is called, which handles the cases of many
131 ;; variations on a single instruction.
132 (declare (type list insts)
133 (type dchunk initial-mask))
139 (let ((vmask (dchunk-copy initial-mask)))
141 (dchunk-andf vmask (inst-mask inst)))
142 (if (dchunk-zerop vmask)
143 (try-specializing insts)
146 (let* ((common-id (dchunk-and (inst-id inst) vmask))
147 (bucket (assoc common-id buckets :test #'dchunk=)))
149 (push (list common-id inst) buckets))
151 (push inst (cdr bucket))))))
152 (let ((submask (dchunk-clear initial-mask vmask)))
153 (if (= (length buckets) 1)
154 (try-specializing insts)
157 :choices (mapcar (lambda (bucket)
158 (make-inst-space-choice
159 :subspace (build-inst-space
162 :common-id (car bucket)))
165 ;;;; an inst-space printer for debugging purposes
167 (defun print-masked-binary (num mask word-size &optional (show word-size))
168 (do ((bit (1- word-size) (1- bit)))
170 (write-char (cond ((logbitp bit mask)
171 (if (logbitp bit num) #\1 #\0))
175 (defun print-inst-bits (inst)
176 (print-masked-binary (inst-id inst)
179 (bytes-to-bits (inst-length inst))))
181 ;;; Print a nicely-formatted version of INST-SPACE.
182 (defun print-inst-space (inst-space &optional (indent 0))
183 (etypecase inst-space
186 (format t "~Vt[~A(~A)~40T" indent
187 (inst-name inst-space)
188 (inst-format-name inst-space))
189 (print-inst-bits inst-space)
190 (dolist (inst (inst-specializers inst-space))
191 (format t "~%~Vt:~A~40T" indent (inst-name inst))
192 (print-inst-bits inst))
196 (format t "~Vt---- ~8,'0X ----~%"
198 (ispace-valid-mask inst-space))
201 (format t "~Vt~8,'0X ==>~%"
203 (ischoice-common-id choice))
204 (print-inst-space (ischoice-subspace choice)
206 (ispace-choices inst-space)))))
208 ;;;; (The actual disassembly part follows.)
210 ;;; Code object layout:
212 ;;; code-size (starting from first inst, in words)
213 ;;; entry-points (points to first function header)
215 ;;; trace-table-offset (starting from first inst, in bytes)
219 ;;; <padding to dual-word boundary>
220 ;;; start of instructions
222 ;;; fun-headers and lra's buried in here randomly
224 ;;; start of trace-table
225 ;;; <padding to dual-word boundary>
227 ;;; Function header layout (dual word aligned):
230 ;;; next pointer (next function header)
235 ;;; LRA layout (dual word aligned):
238 #!-sb-fluid (declaim (inline words-to-bytes bytes-to-words))
240 (eval-when (:compile-toplevel :load-toplevel :execute)
241 ;;; Convert a word-offset NUM to a byte-offset.
242 (defun words-to-bytes (num)
243 (declare (type offset num))
244 (ash num sb!vm:word-shift))
247 ;;; Convert a byte-offset NUM to a word-offset.
248 (defun bytes-to-words (num)
249 (declare (type offset num))
250 (ash num (- sb!vm:word-shift)))
252 (defconstant lra-size (words-to-bytes 1))
254 (defstruct (offs-hook (:copier nil))
255 (offset 0 :type offset)
256 (fun (missing-arg) :type function)
257 (before-address nil :type (member t nil)))
259 (defstruct (segment (:conc-name seg-)
260 (:constructor %make-segment)
262 (sap-maker (missing-arg)
263 :type (function () sb!sys:system-area-pointer))
264 (length 0 :type length)
265 (virtual-location 0 :type address)
266 (storage-info nil :type (or null storage-info))
267 (code nil :type (or null sb!kernel:code-component))
268 (hooks nil :type list))
269 (def!method print-object ((seg segment) stream)
270 (print-unreadable-object (seg stream :type t)
271 (let ((addr (sb!sys:sap-int (funcall (seg-sap-maker seg)))))
272 (format stream "#X~X[~W]~:[ (#X~X)~;~*~]~@[ in ~S~]"
275 (= (seg-virtual-location seg) addr)
276 (seg-virtual-location seg)
281 (defun fun-self (fun)
282 (declare (type compiled-function fun))
283 (sb!kernel:%simple-fun-self fun))
285 (defun fun-code (fun)
286 (declare (type compiled-function fun))
287 (sb!kernel:fun-code-header (fun-self fun)))
289 (defun fun-next (fun)
290 (declare (type compiled-function fun))
291 (sb!kernel:%simple-fun-next fun))
293 (defun fun-address (function)
294 (declare (type compiled-function function))
295 (- (sb!kernel:get-lisp-obj-address function) sb!vm:fun-pointer-lowtag))
297 ;;; the offset of FUNCTION from the start of its code-component's
299 (defun fun-insts-offset (function)
300 (declare (type compiled-function function))
301 (- (fun-address function)
302 (sb!sys:sap-int (sb!kernel:code-instructions (fun-code function)))))
304 ;;; the offset of FUNCTION from the start of its code-component
305 (defun fun-offset (function)
306 (declare (type compiled-function function))
307 (words-to-bytes (sb!kernel:get-closure-length function)))
309 ;;;; operations on code-components (which hold the instructions for
310 ;;;; one or more functions)
312 ;;; Return the length of the instruction area in CODE-COMPONENT.
313 (defun code-inst-area-length (code-component)
314 (declare (type sb!kernel:code-component code-component))
315 (sb!kernel:code-header-ref code-component
316 sb!vm:code-trace-table-offset-slot))
318 ;;; Return the address of the instruction area in CODE-COMPONENT.
319 (defun code-inst-area-address (code-component)
320 (declare (type sb!kernel:code-component code-component))
321 (sb!sys:sap-int (sb!kernel:code-instructions code-component)))
323 ;;; unused as of sbcl-0.pre7.129
325 ;;; Return the first function in CODE-COMPONENT.
326 (defun code-first-function (code-component)
327 (declare (type sb!kernel:code-component code-component))
328 (sb!kernel:code-header-ref code-component
329 sb!vm:code-trace-table-offset-slot))
332 (defun segment-offs-to-code-offs (offset segment)
333 (sb!sys:without-gcing
334 (let* ((seg-base-addr (sb!sys:sap-int (funcall (seg-sap-maker segment))))
336 (logandc1 sb!vm:lowtag-mask
337 (sb!kernel:get-lisp-obj-address (seg-code segment))))
338 (addr (+ offset seg-base-addr)))
339 (declare (type address seg-base-addr code-addr addr))
340 (- addr code-addr))))
342 (defun code-offs-to-segment-offs (offset segment)
343 (sb!sys:without-gcing
344 (let* ((seg-base-addr (sb!sys:sap-int (funcall (seg-sap-maker segment))))
346 (logandc1 sb!vm:lowtag-mask
347 (sb!kernel:get-lisp-obj-address (seg-code segment))))
348 (addr (+ offset code-addr)))
349 (declare (type address seg-base-addr code-addr addr))
350 (- addr seg-base-addr))))
352 (defun code-insts-offs-to-segment-offs (offset segment)
353 (sb!sys:without-gcing
354 (let* ((seg-base-addr (sb!sys:sap-int (funcall (seg-sap-maker segment))))
356 (sb!sys:sap-int (sb!kernel:code-instructions (seg-code segment))))
357 (addr (+ offset code-insts-addr)))
358 (declare (type address seg-base-addr code-insts-addr addr))
359 (- addr seg-base-addr))))
361 (defun lra-hook (chunk stream dstate)
362 (declare (type dchunk chunk)
364 (type (or null stream) stream)
365 (type disassem-state dstate))
366 (when (and (aligned-p (+ (seg-virtual-location (dstate-segment dstate))
367 (dstate-cur-offs dstate))
368 (* 2 sb!vm:n-word-bytes))
370 (= (sb!sys:sap-ref-8 (dstate-segment-sap dstate)
371 (if (eq (dstate-byte-order dstate)
373 (dstate-cur-offs dstate)
374 (+ (dstate-cur-offs dstate)
376 sb!vm:return-pc-header-widetag))
377 (unless (null stream)
378 (princ '.lra stream))
379 (incf (dstate-next-offs dstate) lra-size))
382 ;;; Print the fun-header (entry-point) pseudo-instruction at the
383 ;;; current location in DSTATE to STREAM.
384 (defun fun-header-hook (stream dstate)
385 (declare (type (or null stream) stream)
386 (type disassem-state dstate))
387 (unless (null stream)
388 (let* ((seg (dstate-segment dstate))
389 (code (seg-code seg))
392 (segment-offs-to-code-offs (dstate-cur-offs dstate) seg)))
394 (sb!kernel:code-header-ref code
396 sb!vm:simple-fun-name-slot)))
398 (sb!kernel:code-header-ref code
400 sb!vm:simple-fun-arglist-slot)))
402 (sb!kernel:code-header-ref code
404 sb!vm:simple-fun-type-slot))))
405 (format stream ".~A ~S~:A" 'entry name args)
406 (note (lambda (stream)
407 (format stream "~:S" type)) ; use format to print NIL as ()
409 (incf (dstate-next-offs dstate)
410 (words-to-bytes sb!vm:simple-fun-code-offset)))
412 (defun alignment-hook (chunk stream dstate)
413 (declare (type dchunk chunk)
415 (type (or null stream) stream)
416 (type disassem-state dstate))
418 (+ (seg-virtual-location (dstate-segment dstate))
419 (dstate-cur-offs dstate)))
420 (alignment (dstate-alignment dstate)))
421 (unless (aligned-p location alignment)
423 (format stream "~A~Vt~W~%" '.align
424 (dstate-argument-column dstate)
426 (incf(dstate-next-offs dstate)
427 (- (align location alignment) location)))
430 (defun rewind-current-segment (dstate segment)
431 (declare (type disassem-state dstate)
432 (type segment segment))
433 (setf (dstate-segment dstate) segment)
434 (setf (dstate-cur-offs-hooks dstate)
435 (stable-sort (nreverse (copy-list (seg-hooks segment)))
437 (or (< (offs-hook-offset oh1) (offs-hook-offset oh2))
438 (and (= (offs-hook-offset oh1)
439 (offs-hook-offset oh2))
440 (offs-hook-before-address oh1)
441 (not (offs-hook-before-address oh2)))))))
442 (setf (dstate-cur-offs dstate) 0)
443 (setf (dstate-cur-labels dstate) (dstate-labels dstate)))
445 (defun call-offs-hooks (before-address stream dstate)
446 (declare (type (or null stream) stream)
447 (type disassem-state dstate))
448 (let ((cur-offs (dstate-cur-offs dstate)))
449 (setf (dstate-next-offs dstate) cur-offs)
451 (let ((next-hook (car (dstate-cur-offs-hooks dstate))))
452 (when (null next-hook)
454 (let ((hook-offs (offs-hook-offset next-hook)))
455 (when (or (> hook-offs cur-offs)
456 (and (= hook-offs cur-offs)
458 (not (offs-hook-before-address next-hook))))
460 (unless (< hook-offs cur-offs)
461 (funcall (offs-hook-fun next-hook) stream dstate))
462 (pop (dstate-cur-offs-hooks dstate))
463 (unless (= (dstate-next-offs dstate) cur-offs)
466 (defun call-fun-hooks (chunk stream dstate)
467 (let ((hooks (dstate-fun-hooks dstate))
468 (cur-offs (dstate-cur-offs dstate)))
469 (setf (dstate-next-offs dstate) cur-offs)
470 (dolist (hook hooks nil)
471 (let ((prefix-p (funcall hook chunk stream dstate)))
472 (unless (= (dstate-next-offs dstate) cur-offs)
473 (return prefix-p))))))
475 (defun handle-bogus-instruction (stream dstate)
476 (let ((alignment (dstate-alignment dstate)))
477 (unless (null stream)
478 (multiple-value-bind (words bytes)
479 (truncate alignment sb!vm:n-word-bytes)
481 (print-words words stream dstate))
483 (print-bytes bytes stream dstate))))
484 (incf (dstate-next-offs dstate) alignment)))
486 ;;; Iterate through the instructions in SEGMENT, calling FUNCTION for
487 ;;; each instruction, with arguments of CHUNK, STREAM, and DSTATE.
488 (defun map-segment-instructions (function segment dstate &optional stream)
489 (declare (type function function)
490 (type segment segment)
491 (type disassem-state dstate)
492 (type (or null stream) stream))
494 (let ((ispace (get-inst-space))
495 (prefix-p nil)) ; just processed a prefix inst
497 (rewind-current-segment dstate segment)
500 (when (>= (dstate-cur-offs dstate)
501 (seg-length (dstate-segment dstate)))
505 (setf (dstate-next-offs dstate) (dstate-cur-offs dstate))
507 (call-offs-hooks t stream dstate)
508 (unless (or prefix-p (null stream))
509 (print-current-address stream dstate))
510 (call-offs-hooks nil stream dstate)
512 (unless (> (dstate-next-offs dstate) (dstate-cur-offs dstate))
513 (sb!sys:without-gcing
514 (setf (dstate-segment-sap dstate) (funcall (seg-sap-maker segment)))
517 (sap-ref-dchunk (dstate-segment-sap dstate)
518 (dstate-cur-offs dstate)
519 (dstate-byte-order dstate))))
520 (let ((fun-prefix-p (call-fun-hooks chunk stream dstate)))
521 (if (> (dstate-next-offs dstate) (dstate-cur-offs dstate))
522 (setf prefix-p fun-prefix-p)
523 (let ((inst (find-inst chunk ispace)))
525 (handle-bogus-instruction stream dstate))
527 (setf (dstate-next-offs dstate)
528 (+ (dstate-cur-offs dstate)
531 (let ((prefilter (inst-prefilter inst))
532 (control (inst-control inst)))
534 (funcall prefilter chunk dstate))
536 (funcall function chunk inst)
538 (setf prefix-p (null (inst-printer inst)))
541 (funcall control chunk inst stream dstate))))))
544 (setf (dstate-cur-offs dstate) (dstate-next-offs dstate))
546 (unless (null stream)
548 (print-notes-and-newline stream dstate))
549 (setf (dstate-output-state dstate) nil)))))
551 ;;; Make an initial non-printing disassembly pass through DSTATE,
552 ;;; noting any addresses that are referenced by instructions in this
554 (defun add-segment-labels (segment dstate)
555 ;; add labels at the beginning with a label-number of nil; we'll notice
556 ;; later and fill them in (and sort them)
557 (declare (type disassem-state dstate))
558 (let ((labels (dstate-labels dstate)))
559 (map-segment-instructions
561 (declare (type dchunk chunk) (type instruction inst))
562 (let ((labeller (inst-labeller inst)))
564 (setf labels (funcall labeller chunk labels dstate)))))
567 (setf (dstate-labels dstate) labels)
568 ;; erase any notes that got there by accident
569 (setf (dstate-notes dstate) nil)))
571 ;;; If any labels in DSTATE have been added since the last call to
572 ;;; this function, give them label-numbers, enter them in the
573 ;;; hash-table, and make sure the label list is in sorted order.
574 (defun number-labels (dstate)
575 (let ((labels (dstate-labels dstate)))
576 (when (and labels (null (cdar labels)))
577 ;; at least one label left un-numbered
578 (setf labels (sort labels #'< :key #'car))
580 (label-hash (dstate-label-hash dstate)))
581 (dolist (label labels)
582 (when (not (null (cdr label)))
583 (setf max (max max (cdr label)))))
584 (dolist (label labels)
585 (when (null (cdr label))
587 (setf (cdr label) max)
588 (setf (gethash (car label) label-hash)
589 (format nil "L~W" max)))))
590 (setf (dstate-labels dstate) labels))))
592 ;;; Get the instruction-space, creating it if necessary.
593 (defun get-inst-space ()
594 (let ((ispace *disassem-inst-space*))
597 (maphash (lambda (name inst-flavs)
598 (declare (ignore name))
599 (dolist (flav inst-flavs)
602 (setf ispace (build-inst-space insts)))
603 (setf *disassem-inst-space* ispace))
606 ;;;; Add global hooks.
608 (defun add-offs-hook (segment addr hook)
609 (let ((entry (cons addr hook)))
610 (if (null (seg-hooks segment))
611 (setf (seg-hooks segment) (list entry))
612 (push entry (cdr (last (seg-hooks segment)))))))
614 (defun add-offs-note-hook (segment addr note)
615 (add-offs-hook segment
617 (lambda (stream dstate)
618 (declare (type (or null stream) stream)
619 (type disassem-state dstate))
621 (note note dstate)))))
623 (defun add-offs-comment-hook (segment addr comment)
624 (add-offs-hook segment
626 (lambda (stream dstate)
627 (declare (type (or null stream) stream)
630 (write-string ";;; " stream)
633 (write-string comment stream))
635 (funcall comment stream)))
638 (defun add-fun-hook (dstate function)
639 (push function (dstate-fun-hooks dstate)))
641 (defun set-location-printing-range (dstate from length)
642 (setf (dstate-addr-print-len dstate)
643 ;; 4 bits per hex digit
644 (ceiling (integer-length (logxor from (+ from length))) 4)))
646 ;;; Print the current address in DSTATE to STREAM, plus any labels that
647 ;;; correspond to it, and leave the cursor in the instruction column.
648 (defun print-current-address (stream dstate)
649 (declare (type stream stream)
650 (type disassem-state dstate))
652 (+ (seg-virtual-location (dstate-segment dstate))
653 (dstate-cur-offs dstate)))
654 (location-column-width *disassem-location-column-width*)
655 (plen (dstate-addr-print-len dstate)))
658 (setf plen location-column-width)
659 (let ((seg (dstate-segment dstate)))
660 (set-location-printing-range dstate
661 (seg-virtual-location seg)
663 (when (eq (dstate-output-state dstate) :beginning)
664 (setf plen location-column-width))
668 (setf location-column-width (+ 2 location-column-width))
671 ;; print the location
672 ;; [this is equivalent to (format stream "~V,'0x:" plen printed-value), but
673 ;; usually avoids any consing]
674 (tab0 (- location-column-width plen) stream)
675 (let* ((printed-bits (* 4 plen))
676 (printed-value (ldb (byte printed-bits 0) location))
678 (truncate (- printed-bits (integer-length printed-value)) 4)))
679 (dotimes (i leading-zeros)
680 (write-char #\0 stream))
681 (unless (zerop printed-value)
682 (write printed-value :stream stream :base 16 :radix nil))
683 (write-char #\: stream))
687 (let* ((next-label (car (dstate-cur-labels dstate)))
688 (label-location (car next-label)))
689 (when (or (null label-location) (> label-location location))
691 (unless (< label-location location)
692 (format stream " L~W:" (cdr next-label)))
693 (pop (dstate-cur-labels dstate))))
695 ;; move to the instruction column
696 (tab0 (+ location-column-width 1 label-column-width) stream)
699 (eval-when (:compile-toplevel :execute)
700 (sb!xc:defmacro with-print-restrictions (&rest body)
701 `(let ((*print-pretty* t)
707 ;;; Print a newline to STREAM, inserting any pending notes in DSTATE
708 ;;; as end-of-line comments. If there is more than one note, a
709 ;;; separate line will be used for each one.
710 (defun print-notes-and-newline (stream dstate)
711 (declare (type stream stream)
712 (type disassem-state dstate))
713 (with-print-restrictions
714 (dolist (note (dstate-notes dstate))
715 (format stream "~Vt " *disassem-note-column*)
716 (pprint-logical-block (stream nil :per-line-prefix "; ")
719 (write-string note stream))
721 (funcall note stream))))
724 (setf (dstate-notes dstate) nil)))
726 ;;; Disassemble NUM bytes to STREAM as simple `BYTE' instructions.
727 (defun print-bytes (num stream dstate)
728 (declare (type offset num)
730 (type disassem-state dstate))
731 (format stream "~A~Vt" 'BYTE (dstate-argument-column dstate))
732 (let ((sap (dstate-segment-sap dstate))
733 (start-offs (dstate-cur-offs dstate)))
736 (write-string ", " stream))
737 (format stream "#X~2,'0x" (sb!sys:sap-ref-8 sap (+ offs start-offs))))))
739 ;;; Disassemble NUM machine-words to STREAM as simple `WORD' instructions.
740 (defun print-words (num stream dstate)
741 (declare (type offset num)
743 (type disassem-state dstate))
744 (format stream "~A~Vt" 'WORD (dstate-argument-column dstate))
745 (let ((sap (dstate-segment-sap dstate))
746 (start-offs (dstate-cur-offs dstate))
747 (byte-order (dstate-byte-order dstate)))
748 (dotimes (word-offs num)
749 (unless (zerop word-offs)
750 (write-string ", " stream))
751 (let ((word 0) (bit-shift 0))
752 (dotimes (byte-offs sb!vm:n-word-bytes)
757 (* word-offs sb!vm:n-word-bytes)
760 (if (eq byte-order :big-endian)
761 (+ (ash word sb!vm:n-byte-bits) byte)
762 (+ word (ash byte bit-shift))))
763 (incf bit-shift sb!vm:n-byte-bits)))
764 (format stream "#X~V,'0X" (ash sb!vm:n-word-bits -2) word)))))
766 (defvar *default-dstate-hooks* (list #'lra-hook))
768 ;;; Make a disassembler-state object.
769 (defun make-dstate (&optional (fun-hooks *default-dstate-hooks*))
771 (sb!sys:vector-sap (coerce #() '(vector (unsigned-byte 8)))))
772 (alignment *disassem-inst-alignment-bytes*)
774 (+ (or *disassem-opcode-column-width* 0)
775 *disassem-location-column-width*
777 label-column-width)))
779 (when (> alignment 1)
780 (push #'alignment-hook fun-hooks))
782 (%make-dstate :segment-sap sap
784 :argument-column arg-column
786 :byte-order sb!c:*backend-byte-order*)))
788 (defun add-fun-header-hooks (segment)
789 (declare (type segment segment))
790 (do ((fun (sb!kernel:code-header-ref (seg-code segment)
791 sb!vm:code-entry-points-slot)
793 (length (seg-length segment)))
795 (let ((offset (code-offs-to-segment-offs (fun-offset fun) segment)))
796 (when (<= 0 offset length)
797 (push (make-offs-hook :offset offset :fun #'fun-header-hook)
798 (seg-hooks segment))))))
800 ;;; A SAP-MAKER is a no-argument function that returns a SAP.
802 #!-sb-fluid (declaim (inline sap-maker))
804 (defun sap-maker (function input offset)
805 (declare (optimize (speed 3))
806 (type (function (t) sb!sys:system-area-pointer) function)
807 (type offset offset))
808 (let ((old-sap (sb!sys:sap+ (funcall function input) offset)))
809 (declare (type sb!sys:system-area-pointer old-sap))
812 (+ (sb!sys:sap-int (funcall function input)) offset)))
813 ;; Saving the sap like this avoids consing except when the sap
814 ;; changes (because the sap-int, arith, etc., get inlined).
815 (declare (type address new-addr))
816 (if (= (sb!sys:sap-int old-sap) new-addr)
818 (setf old-sap (sb!sys:int-sap new-addr)))))))
820 (defun vector-sap-maker (vector offset)
821 (declare (optimize (speed 3))
822 (type offset offset))
823 (sap-maker #'sb!sys:vector-sap vector offset))
825 (defun code-sap-maker (code offset)
826 (declare (optimize (speed 3))
827 (type sb!kernel:code-component code)
828 (type offset offset))
829 (sap-maker #'sb!kernel:code-instructions code offset))
831 (defun memory-sap-maker (address)
832 (declare (optimize (speed 3))
833 (type address address))
834 (let ((sap (sb!sys:int-sap address)))
837 ;;; Return a memory segment located at the system-area-pointer returned by
838 ;;; SAP-MAKER and LENGTH bytes long in the disassem-state object DSTATE.
840 ;;; &KEY arguments include :VIRTUAL-LOCATION (by default the same as
841 ;;; the address), :DEBUG-FUN, :SOURCE-FORM-CACHE (a
842 ;;; SOURCE-FORM-CACHE object), and :HOOKS (a list of OFFS-HOOK
844 (defun make-segment (sap-maker length
846 code virtual-location
847 debug-fun source-form-cache
849 (declare (type (function () sb!sys:system-area-pointer) sap-maker)
851 (type (or null address) virtual-location)
852 (type (or null sb!di:debug-fun) debug-fun)
853 (type (or null source-form-cache) source-form-cache))
858 :virtual-location (or virtual-location
859 (sb!sys:sap-int (funcall sap-maker)))
862 (add-debugging-hooks segment debug-fun source-form-cache)
863 (add-fun-header-hooks segment)
866 (defun make-vector-segment (vector offset &rest args)
867 (declare (type vector vector)
869 (inline make-segment))
870 (apply #'make-segment (vector-sap-maker vector offset) args))
872 (defun make-code-segment (code offset length &rest args)
873 (declare (type sb!kernel:code-component code)
875 (inline make-segment))
876 (apply #'make-segment (code-sap-maker code offset) length :code code args))
878 (defun make-memory-segment (address &rest args)
879 (declare (type address address)
880 (inline make-segment))
881 (apply #'make-segment (memory-sap-maker address) args))
884 (defun print-fun-headers (function)
885 (declare (type compiled-function function))
886 (let* ((self (fun-self function))
887 (code (sb!kernel:fun-code-header self)))
888 (format t "Code-header ~S: size: ~S, trace-table-offset: ~S~%"
890 (sb!kernel:code-header-ref code
891 sb!vm:code-code-size-slot)
892 (sb!kernel:code-header-ref code
893 sb!vm:code-trace-table-offset-slot))
894 (do ((fun (sb!kernel:code-header-ref code sb!vm:code-entry-points-slot)
897 (let ((fun-offset (sb!kernel:get-closure-length fun)))
898 ;; There is function header fun-offset words from the
900 (format t "Fun-header ~S at offset ~W (words): ~S~A => ~S~%"
903 (sb!kernel:code-header-ref
904 code (+ fun-offset sb!vm:simple-fun-name-slot))
905 (sb!kernel:code-header-ref
906 code (+ fun-offset sb!vm:simple-fun-arglist-slot))
907 (sb!kernel:code-header-ref
908 code (+ fun-offset sb!vm:simple-fun-type-slot)))))))
910 ;;; getting at the source code...
912 (defstruct (source-form-cache (:conc-name sfcache-)
914 (debug-source nil :type (or null sb!di:debug-source))
915 (toplevel-form-index -1 :type fixnum)
916 (toplevel-form nil :type list)
917 (form-number-mapping-table nil :type (or null (vector list)))
918 (last-location-retrieved nil :type (or null sb!di:code-location))
919 (last-form-retrieved -1 :type fixnum))
921 (defun get-toplevel-form (debug-source tlf-index)
922 (let ((name (sb!di:debug-source-name debug-source)))
923 (ecase (sb!di:debug-source-from debug-source)
925 (cond ((not (probe-file name))
926 (warn "The source file ~S no longer seems to exist." name)
929 (let ((start-positions
930 (sb!di:debug-source-start-positions debug-source)))
931 (cond ((null start-positions)
932 (warn "There is no start positions map.")
935 (let* ((local-tlf-index
937 (sb!di:debug-source-root-number
940 (aref start-positions local-tlf-index)))
941 (with-open-file (f name)
942 (cond ((= (sb!di:debug-source-created debug-source)
943 (file-write-date name))
944 (file-position f char-offset))
946 (warn "Source file ~S has been modified; ~@
947 using form offset instead of ~
950 (let ((*read-suppress* t))
951 (dotimes (i local-tlf-index) (read f)))))
952 (let ((*readtable* (copy-readtable)))
953 (set-dispatch-macro-character
955 (lambda (stream sub-char &rest rest)
956 (declare (ignore rest sub-char))
957 (let ((token (read stream t nil t)))
958 (format nil "#.~S" token))))
962 (aref name tlf-index)))))
964 (defun cache-valid (loc cache)
966 (and (eq (sb!di:code-location-debug-source loc)
967 (sfcache-debug-source cache))
968 (eq (sb!di:code-location-toplevel-form-offset loc)
969 (sfcache-toplevel-form-index cache)))))
971 (defun get-source-form (loc context &optional cache)
972 (let* ((cache-valid (cache-valid loc cache))
973 (tlf-index (sb!di:code-location-toplevel-form-offset loc))
974 (form-number (sb!di:code-location-form-number loc))
977 (sfcache-toplevel-form cache)
978 (get-toplevel-form (sb!di:code-location-debug-source loc)
982 (sfcache-form-number-mapping-table cache)
983 (sb!di:form-number-translations toplevel-form tlf-index))))
984 (when (and (not cache-valid) cache)
985 (setf (sfcache-debug-source cache) (sb!di:code-location-debug-source loc)
986 (sfcache-toplevel-form-index cache) tlf-index
987 (sfcache-toplevel-form cache) toplevel-form
988 (sfcache-form-number-mapping-table cache) mapping-table))
989 (cond ((null toplevel-form)
991 ((> form-number (length mapping-table))
992 (warn "bogus form-number in form! The source file has probably ~@
993 been changed too much to cope with.")
995 ;; Disable future warnings.
996 (setf (sfcache-toplevel-form cache) nil))
1000 (setf (sfcache-last-location-retrieved cache) loc)
1001 (setf (sfcache-last-form-retrieved cache) form-number))
1002 (sb!di:source-path-context toplevel-form
1003 (aref mapping-table form-number)
1006 (defun get-different-source-form (loc context &optional cache)
1007 (if (and (cache-valid loc cache)
1008 (or (= (sb!di:code-location-form-number loc)
1009 (sfcache-last-form-retrieved cache))
1010 (and (sfcache-last-location-retrieved cache)
1011 (sb!di:code-location=
1013 (sfcache-last-location-retrieved cache)))))
1015 (values (get-source-form loc context cache) t)))
1017 ;;;; stuff to use debugging info to augment the disassembly
1019 (defun code-fun-map (code)
1020 (declare (type sb!kernel:code-component code))
1021 (sb!c::compiled-debug-info-fun-map (sb!kernel:%code-debug-info code)))
1023 (defstruct (location-group (:copier nil))
1024 (locations #() :type (vector (or list fixnum))))
1026 (defstruct (storage-info (:copier nil))
1027 (groups nil :type list) ; alist of (name . location-group)
1028 (debug-vars #() :type vector))
1030 ;;; Return the vector of DEBUG-VARs currently associated with DSTATE.
1031 (defun dstate-debug-vars (dstate)
1032 (declare (type disassem-state dstate))
1033 (storage-info-debug-vars (seg-storage-info (dstate-segment dstate))))
1035 ;;; Given the OFFSET of a location within the location-group called
1036 ;;; LG-NAME, see whether there's a current mapping to a source
1037 ;;; variable in DSTATE, and if so, return the offset of that variable
1038 ;;; in the current debug-var vector.
1039 (defun find-valid-storage-location (offset lg-name dstate)
1040 (declare (type offset offset)
1041 (type symbol lg-name)
1042 (type disassem-state dstate))
1043 (let* ((storage-info
1044 (seg-storage-info (dstate-segment dstate)))
1047 (cdr (assoc lg-name (storage-info-groups storage-info)))))
1049 (dstate-current-valid-locations dstate)))
1051 (not (null currently-valid))
1052 (let ((locations (location-group-locations location-group)))
1053 (and (< offset (length locations))
1054 (let ((used-by (aref locations offset)))
1056 (let ((debug-var-num
1060 (zerop (bit currently-valid used-by)))
1066 (bit currently-valid num)))
1071 ;; Found a valid storage reference!
1072 ;; can't use it again until it's revalidated...
1073 (setf (bit (dstate-current-valid-locations
1080 ;;; Return a new vector which has the same contents as the old one
1081 ;;; VEC, plus new cells (for a total size of NEW-LEN). The additional
1082 ;;; elements are initialized to INITIAL-ELEMENT.
1083 (defun grow-vector (vec new-len &optional initial-element)
1084 (declare (type vector vec)
1085 (type fixnum new-len))
1087 (make-sequence `(vector ,(array-element-type vec) ,new-len)
1089 :initial-element initial-element)))
1090 (dotimes (i (length vec))
1091 (setf (aref new i) (aref vec i)))
1094 ;;; Return a STORAGE-INFO struction describing the object-to-source
1095 ;;; variable mappings from DEBUG-FUN.
1096 (defun storage-info-for-debug-fun (debug-fun)
1097 (declare (type sb!di:debug-fun debug-fun))
1098 (let ((sc-vec sb!c::*backend-sc-numbers*)
1100 (debug-vars (sb!di::debug-fun-debug-vars
1103 (dotimes (debug-var-offset
1105 (make-storage-info :groups groups
1106 :debug-vars debug-vars))
1107 (let ((debug-var (aref debug-vars debug-var-offset)))
1109 (format t ";;; At offset ~W: ~S~%" debug-var-offset debug-var)
1111 (sb!di::compiled-debug-var-sc-offset debug-var))
1114 (sb!c:sc-sb (aref sc-vec
1115 (sb!c:sc-offset-scn sc-offset))))))
1117 (format t ";;; SET: ~S[~W]~%"
1118 sb-name (sb!c:sc-offset-offset sc-offset))
1119 (unless (null sb-name)
1120 (let ((group (cdr (assoc sb-name groups))))
1122 (setf group (make-location-group))
1123 (push `(,sb-name . ,group) groups))
1124 (let* ((locations (location-group-locations group))
1125 (length (length locations))
1126 (offset (sb!c:sc-offset-offset sc-offset)))
1127 (when (>= offset length)
1129 (grow-vector locations
1133 (location-group-locations group)
1135 (let ((already-there (aref locations offset)))
1136 (cond ((null already-there)
1137 (setf (aref locations offset) debug-var-offset))
1138 ((eql already-there debug-var-offset))
1140 (if (listp already-there)
1141 (pushnew debug-var-offset
1142 (aref locations offset))
1143 (setf (aref locations offset)
1144 (list debug-var-offset
1149 (defun source-available-p (debug-fun)
1151 (sb!di:do-debug-fun-blocks (block debug-fun)
1152 (declare (ignore block))
1154 (sb!di:no-debug-blocks () nil)))
1156 (defun print-block-boundary (stream dstate)
1157 (let ((os (dstate-output-state dstate)))
1158 (when (not (eq os :beginning))
1159 (when (not (eq os :block-boundary))
1161 (setf (dstate-output-state dstate)
1164 ;;; Add hooks to track to track the source code in SEGMENT during
1165 ;;; disassembly. SFCACHE can be either NIL or it can be a
1166 ;;; SOURCE-FORM-CACHE structure, in which case it is used to cache
1167 ;;; forms from files.
1168 (defun add-source-tracking-hooks (segment debug-fun &optional sfcache)
1169 (declare (type segment segment)
1170 (type (or null sb!di:debug-fun) debug-fun)
1171 (type (or null source-form-cache) sfcache))
1172 (let ((last-block-pc -1))
1173 (flet ((add-hook (pc fun &optional before-address)
1174 (push (make-offs-hook
1175 :offset pc ;; ### FIX to account for non-zero offs in code
1177 :before-address before-address)
1178 (seg-hooks segment))))
1180 (sb!di:do-debug-fun-blocks (block debug-fun)
1181 (let ((first-location-in-block-p t))
1182 (sb!di:do-debug-block-locations (loc block)
1183 (let ((pc (sb!di::compiled-code-location-pc loc)))
1185 ;; Put blank lines in at block boundaries
1186 (when (and first-location-in-block-p
1187 (/= pc last-block-pc))
1188 (setf first-location-in-block-p nil)
1190 (lambda (stream dstate)
1191 (print-block-boundary stream dstate))
1193 (setf last-block-pc pc))
1195 ;; Print out corresponding source; this information is not
1196 ;; all that accurate, but it's better than nothing
1197 (unless (zerop (sb!di:code-location-form-number loc))
1198 (multiple-value-bind (form new)
1199 (get-different-source-form loc 0 sfcache)
1201 (let ((at-block-begin (= pc last-block-pc)))
1204 (lambda (stream dstate)
1205 (declare (ignore dstate))
1207 (unless at-block-begin
1209 (format stream ";;; [~W] "
1210 (sb!di:code-location-form-number
1212 (prin1-short form stream)
1217 ;; Keep track of variable live-ness as best we can.
1219 (copy-seq (sb!di::compiled-code-location-live-set
1223 (lambda (stream dstate)
1224 (declare (ignore stream))
1225 (setf (dstate-current-valid-locations dstate)
1228 (note (lambda (stream)
1229 (let ((*print-length* nil))
1230 (format stream "live set: ~S"
1234 (sb!di:no-debug-blocks () nil)))))
1236 (defun add-debugging-hooks (segment debug-fun &optional sfcache)
1238 (setf (seg-storage-info segment)
1239 (storage-info-for-debug-fun debug-fun))
1240 (add-source-tracking-hooks segment debug-fun sfcache)
1241 (let ((kind (sb!di:debug-fun-kind debug-fun)))
1242 (flet ((add-new-hook (n)
1243 (push (make-offs-hook
1245 :fun (lambda (stream dstate)
1246 (declare (ignore stream))
1248 (seg-hooks segment))))
1252 (add-new-hook "no-arg-parsing entry point"))
1254 (add-new-hook (lambda (stream)
1255 (format stream "~S entry point" kind)))))))))
1257 ;;; Return a list of the segments of memory containing machine code
1258 ;;; instructions for FUNCTION.
1259 (defun get-fun-segments (function)
1260 (declare (type compiled-function function))
1261 (let* ((code (fun-code function))
1262 (fun-map (code-fun-map code))
1263 (fname (sb!kernel:%simple-fun-name function))
1264 (sfcache (make-source-form-cache)))
1265 (let ((first-block-seen-p nil)
1266 (nil-block-seen-p nil)
1268 (last-debug-fun nil)
1270 (flet ((add-seg (offs len df)
1272 (push (make-code-segment code offs len
1274 :source-form-cache sfcache)
1276 (dotimes (fmap-index (length fun-map))
1277 (let ((fmap-entry (aref fun-map fmap-index)))
1278 (etypecase fmap-entry
1280 (when first-block-seen-p
1281 (add-seg last-offset
1282 (- fmap-entry last-offset)
1284 (setf last-debug-fun nil))
1285 (setf last-offset fmap-entry))
1286 (sb!c::compiled-debug-fun
1287 (let ((name (sb!c::compiled-debug-fun-name fmap-entry))
1288 (kind (sb!c::compiled-debug-fun-kind fmap-entry)))
1290 (format t ";;; SAW ~S ~S ~S,~S ~W,~W~%"
1291 name kind first-block-seen-p nil-block-seen-p
1293 (sb!c::compiled-debug-fun-start-pc fmap-entry))
1294 (cond (#+nil (eq last-offset fun-offset)
1295 (and (equal name fname) (not first-block-seen-p))
1296 (setf first-block-seen-p t))
1297 ((eq kind :external)
1298 (when first-block-seen-p
1301 (when nil-block-seen-p
1303 (when first-block-seen-p
1304 (setf nil-block-seen-p t))))
1305 (setf last-debug-fun
1306 (sb!di::make-compiled-debug-fun fmap-entry code)))))))
1307 (let ((max-offset (code-inst-area-length code)))
1308 (when (and first-block-seen-p last-debug-fun)
1309 (add-seg last-offset
1310 (- max-offset last-offset)
1313 (let ((offs (fun-insts-offset function)))
1315 (make-code-segment code offs (- max-offset offs))))
1316 (nreverse segments)))))))
1318 ;;; Return a list of the segments of memory containing machine code
1319 ;;; instructions for the code-component CODE. If START-OFFSET and/or
1320 ;;; LENGTH is supplied, only that part of the code-segment is used
1321 ;;; (but these are constrained to lie within the code-segment).
1322 (defun get-code-segments (code
1325 (length (code-inst-area-length code)))
1326 (declare (type sb!kernel:code-component code)
1327 (type offset start-offset)
1328 (type length length))
1329 (let ((segments nil))
1331 (let ((fun-map (code-fun-map code))
1332 (sfcache (make-source-form-cache)))
1333 (let ((last-offset 0)
1334 (last-debug-fun nil))
1335 (flet ((add-seg (offs len df)
1336 (let* ((restricted-offs
1337 (min (max start-offset offs)
1338 (+ start-offset length)))
1340 (- (min (max start-offset (+ offs len))
1341 (+ start-offset length))
1343 (when (> restricted-len 0)
1344 (push (make-code-segment code
1345 restricted-offs restricted-len
1347 :source-form-cache sfcache)
1349 (dotimes (fun-map-index (length fun-map))
1350 (let ((fun-map-entry (aref fun-map fun-map-index)))
1351 (etypecase fun-map-entry
1353 (add-seg last-offset (- fun-map-entry last-offset)
1355 (setf last-debug-fun nil)
1356 (setf last-offset fun-map-entry))
1357 (sb!c::compiled-debug-fun
1358 (setf last-debug-fun
1359 (sb!di::make-compiled-debug-fun fun-map-entry
1361 (when last-debug-fun
1362 (add-seg last-offset
1363 (- (code-inst-area-length code) last-offset)
1364 last-debug-fun))))))
1366 (make-code-segment code start-offset length)
1367 (nreverse segments))))
1369 ;;; Return two values: the amount by which the last instruction in the
1370 ;;; segment goes past the end of the segment, and the offset of the
1371 ;;; end of the segment from the beginning of that instruction. If all
1372 ;;; instructions fit perfectly, return 0 and 0.
1373 (defun segment-overflow (segment dstate)
1374 (declare (type segment segment)
1375 (type disassem-state dstate))
1376 (let ((seglen (seg-length segment))
1378 (map-segment-instructions (lambda (chunk inst)
1379 (declare (ignore chunk inst))
1380 (setf last-start (dstate-cur-offs dstate)))
1383 (values (- (dstate-cur-offs dstate) seglen)
1384 (- seglen last-start))))
1386 ;;; Compute labels for all the memory segments in SEGLIST and adds
1387 ;;; them to DSTATE. It's important to call this function with all the
1388 ;;; segments you're interested in, so that it can find references from
1390 (defun label-segments (seglist dstate)
1391 (declare (type list seglist)
1392 (type disassem-state dstate))
1393 (dolist (seg seglist)
1394 (add-segment-labels seg dstate))
1395 ;; Now remove any labels that don't point anywhere in the segments
1397 (setf (dstate-labels dstate)
1398 (remove-if (lambda (lab)
1401 (let ((start (seg-virtual-location seg)))
1404 (+ start (seg-length seg)))))
1406 (dstate-labels dstate))))
1408 ;;; Disassemble the machine code instructions in SEGMENT to STREAM.
1409 (defun disassemble-segment (segment stream dstate)
1410 (declare (type segment segment)
1411 (type stream stream)
1412 (type disassem-state dstate))
1413 (let ((*print-pretty* nil)) ; otherwise the pp conses hugely
1414 (number-labels dstate)
1415 (map-segment-instructions
1416 (lambda (chunk inst)
1417 (declare (type dchunk chunk) (type instruction inst))
1418 (let ((printer (inst-printer inst)))
1420 (funcall printer chunk inst stream dstate))))
1425 ;;; Disassemble the machine code instructions in each memory segment
1426 ;;; in SEGMENTS in turn to STREAM.
1427 (defun disassemble-segments (segments stream dstate)
1428 (declare (type list segments)
1429 (type stream stream)
1430 (type disassem-state dstate))
1431 (unless (null segments)
1432 (let ((first (car segments))
1433 (last (car (last segments))))
1434 (set-location-printing-range dstate
1435 (seg-virtual-location first)
1436 (- (+ (seg-virtual-location last)
1438 (seg-virtual-location first)))
1439 (setf (dstate-output-state dstate) :beginning)
1440 (dolist (seg segments)
1441 (disassemble-segment seg stream dstate)))))
1443 ;;;; top level functions
1445 ;;; Disassemble the machine code instructions for FUNCTION.
1446 (defun disassemble-fun (fun &key
1447 (stream *standard-output*)
1449 (declare (type compiled-function fun)
1450 (type stream stream)
1451 (type (member t nil) use-labels))
1452 (let* ((dstate (make-dstate))
1453 (segments (get-fun-segments fun)))
1455 (label-segments segments dstate))
1456 (disassemble-segments segments stream dstate)))
1458 ;;; FIXME: We probably don't need this any more now that there are
1459 ;;; no interpreted functions, only compiled ones.
1460 (defun compile-function-lambda-expr (function)
1461 (declare (type function function))
1462 (multiple-value-bind (lambda closurep name)
1463 (function-lambda-expression function)
1464 (declare (ignore name))
1466 (error "can't compile a lexical closure"))
1467 (compile nil lambda)))
1469 (defun compiled-fun-or-lose (thing &optional (name thing))
1470 (cond ((or (symbolp thing)
1472 (eq (car thing) 'setf)))
1473 (compiled-fun-or-lose (fdefinition thing) thing))
1477 (eq (car thing) 'lambda))
1478 (compile nil thing))
1480 (error "can't make a compiled function from ~S" name))))
1482 (defun disassemble (object &key
1483 (stream *standard-output*)
1486 "Disassemble the compiled code associated with OBJECT, which can be a
1487 function, a lambda expression, or a symbol with a function definition. If
1488 it is not already compiled, the compiler is called to produce something to
1490 (declare (type (or function symbol cons) object)
1491 (type (or (member t) stream) stream)
1492 (type (member t nil) use-labels))
1493 (pprint-logical-block (*standard-output* nil :per-line-prefix "; ")
1494 (disassemble-fun (compiled-fun-or-lose object)
1496 :use-labels use-labels)
1499 ;;; Disassembles the given area of memory starting at ADDRESS and
1500 ;;; LENGTH long. Note that if CODE-COMPONENT is NIL and this memory
1501 ;;; could move during a GC, you'd better disable it around the call to
1503 (defun disassemble-memory (address
1506 (stream *standard-output*)
1509 (declare (type (or address sb!sys:system-area-pointer) address)
1510 (type length length)
1511 (type stream stream)
1512 (type (or null sb!kernel:code-component) code-component)
1513 (type (member t nil) use-labels))
1515 (if (sb!sys:system-area-pointer-p address)
1516 (sb!sys:sap-int address)
1518 (dstate (make-dstate))
1524 (sb!kernel:code-instructions code-component)))))
1525 (when (or (< code-offs 0)
1526 (> code-offs (code-inst-area-length code-component)))
1527 (error "address ~X not in the code component ~S"
1528 address code-component))
1529 (get-code-segments code-component code-offs length))
1530 (list (make-memory-segment address length)))))
1532 (label-segments segments dstate))
1533 (disassemble-segments segments stream dstate)))
1535 ;;; Disassemble the machine code instructions associated with
1536 ;;; CODE-COMPONENT (this may include multiple entry points).
1537 (defun disassemble-code-component (code-component &key
1538 (stream *standard-output*)
1540 (declare (type (or null sb!kernel:code-component compiled-function)
1542 (type stream stream)
1543 (type (member t nil) use-labels))
1544 (let* ((code-component
1545 (if (functionp code-component)
1546 (fun-code code-component)
1548 (dstate (make-dstate))
1549 (segments (get-code-segments code-component)))
1551 (label-segments segments dstate))
1552 (disassemble-segments segments stream dstate)))
1554 ;;; code for making useful segments from arbitrary lists of code-blocks
1556 ;;; the maximum size of an instruction. Note that this includes
1557 ;;; pseudo-instructions like error traps with their associated
1558 ;;; operands, so it should be big enough to include them, i.e. it's
1559 ;;; not just 4 on a risc machine!
1560 (defconstant max-instruction-size 16)
1562 (defun add-block-segments (seg-code-block
1567 (declare (type list seglist)
1568 (type integer location)
1569 (type (or null (vector (unsigned-byte 8))) connecting-vec)
1570 (type disassem-state dstate))
1571 (flet ((addit (seg overflow)
1572 (let ((length (+ (seg-length seg) overflow)))
1574 (setf (seg-length seg) length)
1575 (incf location length)
1576 (push seg seglist)))))
1577 (let ((connecting-overflow 0)
1578 (amount (length seg-code-block)))
1579 (when connecting-vec
1580 ;; Tack on some of the new block to the old overflow vector.
1581 (let* ((beginning-of-block-amount
1582 (if seg-code-block (min max-instruction-size amount) 0))
1586 '(vector (unsigned-byte 8))
1588 (subseq seg-code-block 0 beginning-of-block-amount))
1590 (when (and (< (length connecting-vec) max-instruction-size)
1591 (not (null seg-code-block)))
1592 (return-from add-block-segments
1593 ;; We want connecting vectors to be large enough to hold
1594 ;; any instruction, and since the current seg-code-block
1595 ;; wasn't large enough to do this (and is now entirely
1596 ;; on the end of the overflow-vector), just save it for
1598 (values seglist location connecting-vec)))
1599 (when (> (length connecting-vec) 0)
1601 (make-vector-segment connecting-vec
1603 (- (length connecting-vec)
1604 beginning-of-block-amount)
1605 :virtual-location location)))
1606 (setf connecting-overflow (segment-overflow seg dstate))
1607 (addit seg connecting-overflow)))))
1608 (cond ((null seg-code-block)
1609 ;; nothing more to add
1610 (values seglist location nil))
1611 ((< (- amount connecting-overflow) max-instruction-size)
1612 ;; We can't create a segment with the minimum size
1613 ;; required for an instruction, so just keep on accumulating
1614 ;; in the overflow vector for the time-being.
1617 (subseq seg-code-block connecting-overflow amount)))
1619 ;; Put as much as we can into a new segment, and the rest
1620 ;; into the overflow-vector.
1621 (let* ((initial-length
1622 (- amount connecting-overflow max-instruction-size))
1624 (make-vector-segment seg-code-block
1627 :virtual-location location))
1629 (segment-overflow seg dstate)))
1630 (addit seg overflow)
1633 (subseq seg-code-block
1634 (+ connecting-overflow (seg-length seg))
1637 ;;;; code to disassemble assembler segments
1639 (defun assem-segment-to-disassem-segments (assem-segment dstate)
1640 (declare (type sb!assem:segment assem-segment)
1641 (type disassem-state dstate))
1643 (disassem-segments nil)
1644 (connecting-vec nil))
1645 (sb!assem:on-segment-contents-vectorly
1647 (lambda (seg-code-block)
1648 (multiple-value-setq (disassem-segments location connecting-vec)
1649 (add-block-segments seg-code-block
1654 (when connecting-vec
1655 (setf disassem-segments
1656 (add-block-segments nil
1661 (sort disassem-segments #'< :key #'seg-virtual-location)))
1663 ;;; Disassemble the machine code instructions associated with
1664 ;;; ASSEM-SEGMENT (of type assem:segment).
1665 (defun disassemble-assem-segment (assem-segment stream)
1666 (declare (type sb!assem:segment assem-segment)
1667 (type stream stream))
1668 (let* ((dstate (make-dstate))
1670 (assem-segment-to-disassem-segments assem-segment dstate)))
1671 (label-segments disassem-segments dstate)
1672 (disassemble-segments disassem-segments stream dstate)))
1674 ;;; routines to find things in the Lisp environment
1676 ;;; an alist of (SYMBOL-SLOT-OFFSET . ACCESS-FUN-NAME) for slots
1677 ;;; in a symbol object that we know about
1678 (defparameter *grokked-symbol-slots*
1679 (sort `((,sb!vm:symbol-value-slot . symbol-value)
1680 (,sb!vm:symbol-plist-slot . symbol-plist)
1681 (,sb!vm:symbol-name-slot . symbol-name)
1682 (,sb!vm:symbol-package-slot . symbol-package))
1686 ;;; Given ADDRESS, try and figure out if which slot of which symbol is
1687 ;;; being referred to. Of course we can just give up, so it's not a
1688 ;;; big deal... Return two values, the symbol and the name of the
1689 ;;; access function of the slot.
1690 (defun grok-symbol-slot-ref (address)
1691 (declare (type address address))
1692 (if (not (aligned-p address sb!vm:n-word-bytes))
1694 (do ((slots-tail *grokked-symbol-slots* (cdr slots-tail)))
1697 (let* ((field (car slots-tail))
1698 (slot-offset (words-to-bytes (car field)))
1699 (maybe-symbol-addr (- address slot-offset))
1701 (sb!kernel:make-lisp-obj
1702 (+ maybe-symbol-addr sb!vm:other-pointer-lowtag))))
1703 (when (symbolp maybe-symbol)
1704 (return (values maybe-symbol (cdr field))))))))
1706 (defvar *address-of-nil-object* (sb!kernel:get-lisp-obj-address nil))
1708 ;;; Given a BYTE-OFFSET from NIL, try and figure out which slot of
1709 ;;; which symbol is being referred to. Of course we can just give up,
1710 ;;; so it's not a big deal... Return two values, the symbol and the
1711 ;;; access function.
1712 (defun grok-nil-indexed-symbol-slot-ref (byte-offset)
1713 (declare (type offset byte-offset))
1714 (grok-symbol-slot-ref (+ *address-of-nil-object* byte-offset)))
1716 ;;; Return the Lisp object located BYTE-OFFSET from NIL.
1717 (defun get-nil-indexed-object (byte-offset)
1718 (declare (type offset byte-offset))
1719 (sb!kernel:make-lisp-obj (+ *address-of-nil-object* byte-offset)))
1721 ;;; Return two values; the Lisp object located at BYTE-OFFSET in the
1722 ;;; constant area of the code-object in the current segment and T, or
1723 ;;; NIL and NIL if there is no code-object in the current segment.
1724 (defun get-code-constant (byte-offset dstate)
1726 (declare (type offset byte-offset)
1727 (type disassem-state dstate))
1728 (let ((code (seg-code (dstate-segment dstate))))
1731 (sb!kernel:code-header-ref code
1733 sb!vm:other-pointer-lowtag)
1734 (- sb!vm:word-shift)))
1738 (defun get-code-constant-absolute (addr dstate)
1739 (declare (type address addr))
1740 (declare (type disassem-state dstate))
1741 (let ((code (seg-code (dstate-segment dstate))))
1743 (return-from get-code-constant-absolute (values nil nil)))
1744 (let ((code-size (ash (sb!kernel:get-header-data code) sb!vm:word-shift)))
1745 (sb!sys:without-gcing
1746 (let ((code-addr (- (sb!kernel:get-lisp-obj-address code)
1747 sb!vm:other-pointer-lowtag)))
1748 (if (or (< addr code-addr) (>= addr (+ code-addr code-size)))
1750 (values (sb!kernel:code-header-ref
1752 (ash (- addr code-addr) (- sb!vm:word-shift)))
1755 (defvar *assembler-routines-by-addr* nil)
1757 (defvar *foreign-symbols-by-addr* nil)
1759 ;;; Build an address-name hash-table from the name-address hash
1760 (defun invert-address-hash (htable &optional (addr-hash (make-hash-table)))
1761 (maphash (lambda (name address)
1762 (setf (gethash address addr-hash) name))
1766 ;;; Return the name of the primitive Lisp assembler routine or foreign
1767 ;;; symbol located at ADDRESS, or NIL if there isn't one.
1768 (defun find-assembler-routine (address)
1769 (declare (type address address))
1770 (when (null *assembler-routines-by-addr*)
1771 (setf *assembler-routines-by-addr*
1772 (invert-address-hash sb!fasl:*assembler-routines*))
1773 (setf *assembler-routines-by-addr*
1774 (invert-address-hash sb!fasl:*static-foreign-symbols*
1775 *assembler-routines-by-addr*)))
1776 (gethash address *assembler-routines-by-addr*))
1778 ;;;; some handy function for machine-dependent code to use...
1780 #!-sb-fluid (declaim (maybe-inline sap-ref-int read-suffix))
1782 (defun sap-ref-int (sap offset length byte-order)
1783 (declare (type sb!sys:system-area-pointer sap)
1784 (type (unsigned-byte 16) offset)
1785 (type (member 1 2 4) length)
1786 (type (member :little-endian :big-endian) byte-order)
1787 (optimize (speed 3) (safety 0)))
1789 (1 (sb!sys:sap-ref-8 sap offset))
1790 (2 (if (eq byte-order :big-endian)
1791 (+ (ash (sb!sys:sap-ref-8 sap offset) 8)
1792 (sb!sys:sap-ref-8 sap (+ offset 1)))
1793 (+ (ash (sb!sys:sap-ref-8 sap (+ offset 1)) 8)
1794 (sb!sys:sap-ref-8 sap offset))))
1795 (4 (if (eq byte-order :big-endian)
1796 (+ (ash (sb!sys:sap-ref-8 sap offset) 24)
1797 (ash (sb!sys:sap-ref-8 sap (+ 1 offset)) 16)
1798 (ash (sb!sys:sap-ref-8 sap (+ 2 offset)) 8)
1799 (sb!sys:sap-ref-8 sap (+ 3 offset)))
1800 (+ (sb!sys:sap-ref-8 sap offset)
1801 (ash (sb!sys:sap-ref-8 sap (+ 1 offset)) 8)
1802 (ash (sb!sys:sap-ref-8 sap (+ 2 offset)) 16)
1803 (ash (sb!sys:sap-ref-8 sap (+ 3 offset)) 24))))))
1805 (defun read-suffix (length dstate)
1806 (declare (type (member 8 16 32) length)
1807 (type disassem-state dstate)
1808 (optimize (speed 3) (safety 0)))
1809 (let ((length (ecase length (8 1) (16 2) (32 4))))
1810 (declare (type (unsigned-byte 3) length))
1812 (sap-ref-int (dstate-segment-sap dstate)
1813 (dstate-next-offs dstate)
1815 (dstate-byte-order dstate))
1816 (incf (dstate-next-offs dstate) length))))
1818 ;;;; optional routines to make notes about code
1820 ;;; Store NOTE (which can be either a string or a function with a
1821 ;;; single stream argument) to be printed as an end-of-line comment
1822 ;;; after the current instruction is disassembled.
1823 (defun note (note dstate)
1824 (declare (type (or string function) note)
1825 (type disassem-state dstate))
1826 (push note (dstate-notes dstate)))
1828 (defun prin1-short (thing stream)
1829 (with-print-restrictions
1830 (prin1 thing stream)))
1832 (defun prin1-quoted-short (thing stream)
1833 (if (self-evaluating-p thing)
1834 (prin1-short thing stream)
1835 (prin1-short `',thing stream)))
1837 ;;; Store a note about the lisp constant located BYTE-OFFSET bytes
1838 ;;; from the current code-component, to be printed as an end-of-line
1839 ;;; comment after the current instruction is disassembled.
1840 (defun note-code-constant (byte-offset dstate)
1841 (declare (type offset byte-offset)
1842 (type disassem-state dstate))
1843 (multiple-value-bind (const valid)
1844 (get-code-constant byte-offset dstate)
1846 (note (lambda (stream)
1847 (prin1-quoted-short const stream))
1851 ;;; Store a note about the lisp constant located at ADDR in the
1852 ;;; current code-component, to be printed as an end-of-line comment
1853 ;;; after the current instruction is disassembled.
1854 (defun note-code-constant-absolute (addr dstate)
1855 (declare (type address addr)
1856 (type disassem-state dstate))
1857 (multiple-value-bind (const valid)
1858 (get-code-constant-absolute addr dstate)
1860 (note (lambda (stream)
1861 (prin1-quoted-short const stream))
1863 (values const valid)))
1865 ;;; If the memory address located NIL-BYTE-OFFSET bytes from the
1866 ;;; constant NIL is a valid slot in a symbol, store a note describing
1867 ;;; which symbol and slot, to be printed as an end-of-line comment
1868 ;;; after the current instruction is disassembled. Returns non-NIL iff
1869 ;;; a note was recorded.
1870 (defun maybe-note-nil-indexed-symbol-slot-ref (nil-byte-offset dstate)
1871 (declare (type offset nil-byte-offset)
1872 (type disassem-state dstate))
1873 (multiple-value-bind (symbol access-fun)
1874 (grok-nil-indexed-symbol-slot-ref nil-byte-offset)
1876 (note (lambda (stream)
1877 (prin1 (if (eq access-fun 'symbol-value)
1879 `(,access-fun ',symbol))
1884 ;;; If the memory address located NIL-BYTE-OFFSET bytes from the
1885 ;;; constant NIL is a valid lisp object, store a note describing which
1886 ;;; symbol and slot, to be printed as an end-of-line comment after the
1887 ;;; current instruction is disassembled. Returns non-NIL iff a note
1889 (defun maybe-note-nil-indexed-object (nil-byte-offset dstate)
1890 (declare (type offset nil-byte-offset)
1891 (type disassem-state dstate))
1892 (let ((obj (get-nil-indexed-object nil-byte-offset)))
1893 (note (lambda (stream)
1894 (prin1-quoted-short obj stream))
1898 ;;; If ADDRESS is the address of a primitive assembler routine or
1899 ;;; foreign symbol, store a note describing which one, to be printed
1900 ;;; as an end-of-line comment after the current instruction is
1901 ;;; disassembled. Returns non-NIL iff a note was recorded. If
1902 ;;; NOTE-ADDRESS-P is non-NIL, a note of the address is also made.
1903 (defun maybe-note-assembler-routine (address note-address-p dstate)
1904 (declare (type disassem-state dstate))
1905 (unless (typep address 'address)
1906 (return-from maybe-note-assembler-routine nil))
1907 (let ((name (find-assembler-routine address)))
1909 (note (lambda (stream)
1911 (format stream "#x~8,'0x: ~a" address name)
1912 (princ name stream)))
1916 ;;; If there's a valid mapping from OFFSET in the storage class
1917 ;;; SC-NAME to a source variable, make a note of the source-variable
1918 ;;; name, to be printed as an end-of-line comment after the current
1919 ;;; instruction is disassembled. Returns non-NIL iff a note was
1921 (defun maybe-note-single-storage-ref (offset sc-name dstate)
1922 (declare (type offset offset)
1923 (type symbol sc-name)
1924 (type disassem-state dstate))
1925 (let ((storage-location
1926 (find-valid-storage-location offset sc-name dstate)))
1927 (when storage-location
1928 (note (lambda (stream)
1929 (princ (sb!di:debug-var-symbol
1930 (aref (storage-info-debug-vars
1931 (seg-storage-info (dstate-segment dstate)))
1937 ;;; If there's a valid mapping from OFFSET in the storage-base called
1938 ;;; SB-NAME to a source variable, make a note equating ASSOC-WITH with
1939 ;;; the source-variable name, to be printed as an end-of-line comment
1940 ;;; after the current instruction is disassembled. Returns non-NIL iff
1941 ;;; a note was recorded.
1942 (defun maybe-note-associated-storage-ref (offset sb-name assoc-with dstate)
1943 (declare (type offset offset)
1944 (type symbol sb-name)
1945 (type (or symbol string) assoc-with)
1946 (type disassem-state dstate))
1947 (let ((storage-location
1948 (find-valid-storage-location offset sb-name dstate)))
1949 (when storage-location
1950 (note (lambda (stream)
1951 (format stream "~A = ~S"
1953 (sb!di:debug-var-symbol
1954 (aref (dstate-debug-vars dstate)
1960 (defun get-internal-error-name (errnum)
1961 (car (svref sb!c:*backend-internal-errors* errnum)))
1963 (defun get-sc-name (sc-offs)
1964 (sb!c::location-print-name
1965 ;; FIXME: This seems like an awful lot of computation just to get a name.
1966 ;; Couldn't we just use lookup in *BACKEND-SC-NAMES*, without having to cons
1968 (sb!c:make-random-tn :kind :normal
1969 :sc (svref sb!c:*backend-sc-numbers*
1970 (sb!c:sc-offset-scn sc-offs))
1971 :offset (sb!c:sc-offset-offset sc-offs))))
1973 ;;; When called from an error break instruction's :DISASSEM-CONTROL (or
1974 ;;; :DISASSEM-PRINTER) function, will correctly deal with printing the
1975 ;;; arguments to the break.
1977 ;;; ERROR-PARSE-FUN should be a function that accepts:
1978 ;;; 1) a SYSTEM-AREA-POINTER
1979 ;;; 2) a BYTE-OFFSET from the SAP to begin at
1980 ;;; 3) optionally, LENGTH-ONLY, which if non-NIL, means to only return
1981 ;;; the byte length of the arguments (to avoid unnecessary consing)
1982 ;;; It should read information from the SAP starting at BYTE-OFFSET, and
1983 ;;; return four values:
1984 ;;; 1) the error number
1985 ;;; 2) the total length, in bytes, of the information
1986 ;;; 3) a list of SC-OFFSETs of the locations of the error parameters
1987 ;;; 4) a list of the length (as read from the SAP), in bytes, of each
1988 ;;; of the return values.
1989 (defun handle-break-args (error-parse-fun stream dstate)
1990 (declare (type function error-parse-fun)
1991 (type (or null stream) stream)
1992 (type disassem-state dstate))
1993 (multiple-value-bind (errnum adjust sc-offsets lengths)
1994 (funcall error-parse-fun
1995 (dstate-segment-sap dstate)
1996 (dstate-next-offs dstate)
1999 (setf (dstate-cur-offs dstate)
2000 (dstate-next-offs dstate))
2001 (flet ((emit-err-arg (note)
2002 (let ((num (pop lengths)))
2003 (print-notes-and-newline stream dstate)
2004 (print-current-address stream dstate)
2005 (print-bytes num stream dstate)
2006 (incf (dstate-cur-offs dstate) num)
2008 (note note dstate)))))
2010 (emit-err-arg (symbol-name (get-internal-error-name errnum)))
2011 (dolist (sc-offs sc-offsets)
2012 (emit-err-arg (get-sc-name sc-offs)))))
2013 (incf (dstate-next-offs dstate)