1 ;;;; machine-independent disassembler
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 ;;; types and defaults
16 (def!constant label-column-width 7)
18 (deftype text-width () '(integer 0 1000))
19 (deftype alignment () '(integer 0 64))
20 (deftype offset () '(signed-byte 24))
21 (deftype address () '(unsigned-byte 32))
22 (deftype length () '(unsigned-byte 24))
23 (deftype column () '(integer 0 1000))
25 (def!constant max-filtered-value-index 32)
26 (deftype filtered-value-index ()
27 `(integer 0 ,max-filtered-value-index))
28 (deftype filtered-value-vector ()
29 `(simple-array t (,max-filtered-value-index)))
31 ;;;; disassembly parameters
34 (defvar *disassem-insts* (make-hash-table :test 'eq))
35 (declaim (type hash-table *disassem-insts*))
37 (defvar *disassem-inst-space* nil)
39 ;;; minimum alignment of instructions, in bytes
40 (defvar *disassem-inst-alignment-bytes* sb!vm:n-word-bytes)
41 (declaim (type alignment *disassem-inst-alignment-bytes*))
43 (defvar *disassem-location-column-width* 8)
44 (declaim (type text-width *disassem-location-column-width*))
46 ;;; the width of the column in which instruction-names are printed. A
47 ;;; value of zero gives the effect of not aligning the arguments at
49 (defvar *disassem-opcode-column-width* 6)
50 (declaim (type text-width *disassem-opcode-column-width*))
52 (defvar *disassem-note-column* 45
54 "The column in which end-of-line comments for notes are started.")
56 ;;; the old CMU CL code to set the CMU CL disassembly parameters
58 (defmacro set-disassem-params (&rest args)
60 "Specify global disassembler params. &KEY arguments include:
62 :INSTRUCTION-ALIGNMENT number
63 Minimum alignment of instructions, in bits.
66 Size of a machine address, in bits.
69 Width of the column used for printing the opcode portion of the
70 instruction, or NIL to use the default."
71 (gen-preamble-form args))
73 (defun gen-preamble-form (args)
75 "Generate a form to specify global disassembler params. See the
76 documentation for SET-DISASSEM-PARAMS for more info."
78 (&key instruction-alignment
80 (opcode-column-width nil opcode-column-width-p))
83 (eval-when (:compile-toplevel :execute)
84 ;; these are not in the params because they only exist at compile time
85 (defparameter ,(format-table-name) (make-hash-table))
86 (defparameter ,(arg-type-table-name) nil)
87 (defparameter ,(fun-cache-name) (make-fun-cache)))
89 (or sb!c:*backend-disassem-params*
90 (setf sb!c:*backend-disassem-params* (make-params)))))
91 (declare (ignorable params))
92 ,(when instruction-alignment
93 `(setf (params-instruction-alignment params)
94 (bits-to-bytes ,instruction-alignment)))
96 `(setf (params-location-column-width params)
98 ,(when opcode-column-width-p
99 `(setf (params-opcode-column-width params) ,opcode-column-width))
103 ;;;; cached functions
105 ;;;; FIXME: Is it important to cache these? For performance? Or why?
106 ;;;; If performance: *Really*? How fast does disassembly need to be??
107 ;;;; So: Could we just punt this?
109 (defstruct (fun-cache (:copier nil))
110 (printers nil :type list)
111 (labellers nil :type list)
112 (prefilters nil :type list))
114 (defvar *disassem-fun-cache* (make-fun-cache))
115 (declaim (type fun-cache *disassem-fun-cache*))
117 ;;;; A DCHUNK contains the bits we look at to decode an
119 ;;;; I tried to keep this abstract so that if using integers > the machine
120 ;;;; word size conses too much, it can be changed to use bit-vectors or
123 ;;;; KLUDGE: It's not clear that using bit-vectors would be any more efficient.
124 ;;;; Perhaps the abstraction could go away. -- WHN 19991124
127 (declaim (inline dchunk-or dchunk-and dchunk-clear dchunk-not
128 dchunk-make-mask dchunk-make-field
134 (def!constant dchunk-bits 32)
137 `(unsigned-byte ,dchunk-bits))
138 (deftype dchunk-index ()
139 `(integer 0 ,dchunk-bits))
141 (def!constant dchunk-zero 0)
142 (def!constant dchunk-one #xFFFFFFFF)
144 (defun dchunk-extract (from pos)
145 (declare (type dchunk from))
146 (the dchunk (ldb pos (the dchunk from))))
148 (defmacro dchunk-copy (x)
151 (defun dchunk-or (to from)
152 (declare (type dchunk to from))
153 (the dchunk (logior to from)))
154 (defun dchunk-and (to from)
155 (declare (type dchunk to from))
156 (the dchunk (logand to from)))
157 (defun dchunk-clear (to from)
158 (declare (type dchunk to from))
159 (the dchunk (logandc2 to from)))
160 (defun dchunk-not (from)
161 (declare (type dchunk from))
162 (the dchunk (logand dchunk-one (lognot from))))
164 (defmacro dchunk-andf (to from)
165 `(setf ,to (dchunk-and ,to ,from)))
166 (defmacro dchunk-orf (to from)
167 `(setf ,to (dchunk-or ,to ,from)))
168 (defmacro dchunk-clearf (to from)
169 `(setf ,to (dchunk-clear ,to ,from)))
171 (defun dchunk-make-mask (pos)
172 (the dchunk (mask-field pos -1)))
173 (defun dchunk-make-field (pos value)
174 (the dchunk (dpb value pos 0)))
176 (defmacro make-dchunk (value)
177 `(the dchunk ,value))
179 (defun sap-ref-dchunk (sap byte-offset byte-order)
180 (declare (type sb!sys:system-area-pointer sap)
181 (type offset byte-offset)
182 (optimize (speed 3) (safety 0)))
184 (if (eq byte-order :big-endian)
185 (+ (ash (sb!sys:sap-ref-8 sap byte-offset) 24)
186 (ash (sb!sys:sap-ref-8 sap (+ 1 byte-offset)) 16)
187 (ash (sb!sys:sap-ref-8 sap (+ 2 byte-offset)) 8)
188 (sb!sys:sap-ref-8 sap (+ 3 byte-offset)))
189 (+ (sb!sys:sap-ref-8 sap byte-offset)
190 (ash (sb!sys:sap-ref-8 sap (+ 1 byte-offset)) 8)
191 (ash (sb!sys:sap-ref-8 sap (+ 2 byte-offset)) 16)
192 (ash (sb!sys:sap-ref-8 sap (+ 3 byte-offset)) 24)))))
194 (defun dchunk-corrected-extract (from pos unit-bits byte-order)
195 (declare (type dchunk from))
196 (if (eq byte-order :big-endian)
197 (ldb (byte (byte-size pos)
198 (+ (byte-position pos) (- dchunk-bits unit-bits)))
200 (ldb pos (the dchunk from))))
202 (defmacro dchunk-insertf (place pos value)
203 `(setf ,place (the dchunk (dpb ,value ,pos (the dchunk,place)))))
206 (declare (type dchunk x y))
208 (defmacro dchunk-zerop (x)
209 `(dchunk= ,x dchunk-zero))
211 (defun dchunk-strict-superset-p (sup sub)
212 (and (zerop (logandc2 sub sup))
213 (not (zerop (logandc2 sup sub)))))
215 (defun dchunk-count-bits (x)
216 (declare (type dchunk x))
219 (defstruct (instruction (:conc-name inst-)
221 make-instruction (name
227 labeller prefilter control))
229 (name nil :type (or symbol string))
230 (format-name nil :type (or symbol string))
232 (mask dchunk-zero :type dchunk) ; bits in the inst that are constant
233 (id dchunk-zero :type dchunk) ; value of those constant bits
235 (length 0 :type length) ; in bytes
237 (print-name nil :type symbol)
239 ;; disassembly functions
240 (prefilter nil :type (or null function))
241 (labeller nil :type (or null function))
242 (printer (missing-arg) :type (or null function))
243 (control nil :type (or null function))
245 ;; instructions that are the same as this instruction but with more
247 (specializers nil :type list))
248 (def!method print-object ((inst instruction) stream)
249 (print-unreadable-object (inst stream :type t :identity t)
250 (format stream "~A(~A)" (inst-name inst) (inst-format-name inst))))
252 ;;;; an instruction space holds all known machine instructions in a
253 ;;;; form that can be easily searched
255 (defstruct (inst-space (:conc-name ispace-)
257 (valid-mask dchunk-zero :type dchunk) ; applies to *children*
258 (choices nil :type list))
259 (def!method print-object ((ispace inst-space) stream)
260 (print-unreadable-object (ispace stream :type t :identity t)))
262 ;;; now that we've defined the structure, we can declaim the type of
264 (declaim (type (or null inst-space) *disassem-inst-space*))
266 (defstruct (inst-space-choice (:conc-name ischoice-)
268 (common-id dchunk-zero :type dchunk) ; applies to *parent's* mask
269 (subspace (missing-arg) :type (or inst-space instruction)))
271 ;;;; These are the kind of values we can compute for an argument, and
272 ;;;; how to compute them. The :CHECKER functions make sure that a given
273 ;;;; argument is compatible with another argument for a given use.
275 (defvar *arg-form-kinds* nil)
277 (defstruct (arg-form-kind (:copier nil))
278 (names nil :type list)
279 (producer (missing-arg) :type function)
280 (checker (missing-arg) :type function))
282 (defun arg-form-kind-or-lose (kind)
283 (or (getf *arg-form-kinds* kind)
284 (pd-error "unknown arg-form kind ~S" kind)))
286 (defun find-arg-form-producer (kind)
287 (arg-form-kind-producer (arg-form-kind-or-lose kind)))
288 (defun find-arg-form-checker (kind)
289 (arg-form-kind-checker (arg-form-kind-or-lose kind)))
291 (defun canonicalize-arg-form-kind (kind)
292 (car (arg-form-kind-names (arg-form-kind-or-lose kind))))
294 ;;;; only used during compilation of the instructions for a backend
296 ;;;; FIXME: If only used then, isn't there some way we could do
297 ;;;; EVAL-WHEN tricks to keep this stuff from appearing in the target
300 (defvar *disassem-inst-formats* (make-hash-table))
301 (defvar *disassem-arg-types* nil)
302 (defvar *disassem-fun-cache* (make-fun-cache))
304 (defstruct (arg (:copier nil)
306 (name nil :type symbol)
307 (fields nil :type list)
309 (value nil :type (or list integer))
310 (sign-extend-p nil :type (member t nil))
312 ;; position in a vector of prefiltered values
313 (position 0 :type fixnum)
320 (defstruct (instruction-format (:conc-name format-)
323 (args nil :type list)
325 (length 0 :type length) ; in bytes
327 (default-printer nil :type list))
329 ;;; A FUNSTATE holds the state of any arguments used in a disassembly
331 (defstruct (funstate (:conc-name funstate-)
332 (:constructor %make-funstate)
334 (args nil :type list)
335 (arg-temps nil :type list)) ; See below.
337 (defun make-funstate (args)
338 ;; give the args a position
341 (setf (arg-position arg) i)
343 (%make-funstate :args args))
345 (defun funstate-compatible-p (funstate args)
346 (every (lambda (this-arg-temps)
347 (let* ((old-arg (car this-arg-temps))
348 (new-arg (find (arg-name old-arg) args :key #'arg-name)))
350 (every (lambda (this-kind-temps)
351 (funcall (find-arg-form-checker
352 (car this-kind-temps))
355 (cdr this-arg-temps)))))
356 (funstate-arg-temps funstate)))
358 (defun arg-or-lose (name funstate)
359 (let ((arg (find name (funstate-args funstate) :key #'arg-name)))
361 (pd-error "unknown argument ~S" name))
364 ;;;; Since we can't include some values in compiled output as they are
365 ;;;; (notably functions), we sometimes use a VALSRC structure to keep
366 ;;;; track of the source from which they were derived.
368 (defstruct (valsrc (:constructor %make-valsrc)
373 (defun make-valsrc (value source)
374 (cond ((equal value source)
376 ((and (listp value) (eq (car value) 'function))
379 (%make-valsrc :value value :source source))))
381 ;;; machinery to provide more meaningful error messages during compilation
382 (defvar *current-instruction-flavor* nil)
383 (defun pd-error (fmt &rest args)
384 (if *current-instruction-flavor*
385 (error "~@<in printer-definition for ~S(~S): ~3I~:_~?~:>"
386 (car *current-instruction-flavor*)
387 (cdr *current-instruction-flavor*)
389 (apply #'error fmt args)))
392 ;;; 1. This should become a utility in SB!INT.
393 ;;; 2. Arrays and structures and maybe other things are
394 ;;; self-evaluating too.
395 (defun self-evaluating-p (x)
403 (defun maybe-quote (evalp form)
404 (if (or evalp (self-evaluating-p form)) form `',form))
406 ;;; Detect things that obviously don't need wrapping, like
407 ;;; variable-refs and #'function.
408 (defun doesnt-need-wrapping-p (form)
411 (eq (car form) 'function)
412 (symbolp (cadr form)))))
414 (defun make-wrapper (form arg-name funargs prefix)
415 (if (and (listp form)
416 (eq (car form) 'function))
418 (let ((wrapper-name (symbolicate prefix "-" arg-name "-WRAPPER"))
419 (wrapper-args (make-gensym-list (length funargs))))
420 (values `#',wrapper-name
421 `(defun ,wrapper-name ,wrapper-args
422 (funcall ,form ,@wrapper-args))))
424 (let ((wrapper-name (symbolicate "*" prefix "-" arg-name "-WRAPPER*")))
425 (values wrapper-name `(defparameter ,wrapper-name ,form)))))
427 (defun filter-overrides (overrides evalp)
428 (mapcar (lambda (override)
429 (list* (car override) (cadr override)
430 (munge-fun-refs (cddr override) evalp)))
433 (defparameter *arg-fun-params*
434 '((:printer . (value stream dstate))
435 (:use-label . (value dstate))
436 (:prefilter . (value dstate))))
438 (defun munge-fun-refs (params evalp &optional wrap-defs-p (prefix ""))
439 (let ((params (copy-list params)))
440 (do ((tail params (cdr tail))
443 (values params (nreverse wrapper-defs)))
444 (let ((fun-arg (assoc (car tail) *arg-fun-params*)))
446 (let* ((fun-form (cadr tail))
447 (quoted-fun-form `',fun-form))
448 (when (and wrap-defs-p (not (doesnt-need-wrapping-p fun-form)))
449 (multiple-value-bind (access-form wrapper-def-form)
450 (make-wrapper fun-form (car fun-arg) (cdr fun-arg) prefix)
451 (setf quoted-fun-form `',access-form)
452 (push wrapper-def-form wrapper-defs)))
455 `(make-valsrc ,fun-form ,quoted-fun-form))
459 (defun gen-args-def-form (overrides format-form &optional (evalp t))
460 (let ((args-var (gensym)))
461 `(let ((,args-var (copy-list (format-args ,format-form))))
462 ,@(mapcar (lambda (override)
463 (update-args-form args-var
466 (cons :value (cdr override)))
471 (defun gen-printer-def-forms-def-form (base-name
476 (declare (type symbol base-name))
477 (declare (type (or symbol string) uniquified-name))
481 &optional (printer-form :default)
482 &key ((:print-name print-name-form) `',base-name) control)
484 (let ((format-var (gensym))
485 (field-defs (filter-overrides field-defs evalp)))
486 `(let* ((*current-instruction-flavor* ',(cons base-name format-name))
487 (,format-var (format-or-lose ',format-name))
488 (args ,(gen-args-def-form field-defs format-var evalp))
489 (funcache *disassem-fun-cache*))
490 (multiple-value-bind (printer-fun printer-defun)
491 (find-printer-fun ',uniquified-name
493 ,(if (eq printer-form :default)
494 `(format-default-printer ,format-var)
495 (maybe-quote evalp printer-form))
497 (multiple-value-bind (labeller-fun labeller-defun)
498 (find-labeller-fun ',uniquified-name args funcache)
499 (multiple-value-bind (prefilter-fun prefilter-defun)
500 (find-prefilter-fun ',uniquified-name
504 (multiple-value-bind (mask id)
505 (compute-mask-id args)
507 `(make-instruction ',',base-name
510 ,(format-length ,format-var)
513 ,(and printer-fun `#',printer-fun)
514 ,(and labeller-fun `#',labeller-fun)
515 ,(and prefilter-fun `#',prefilter-fun)
518 ,@(and printer-defun (list printer-defun))
519 ,@(and labeller-defun (list labeller-defun))
520 ,@(and prefilter-defun (list prefilter-defun))))
523 (defun update-args-form (var name-form descrip-forms evalp
524 &optional format-length-form)
527 `(modify-or-add-arg ,name-form
530 ,@(and format-length-form
532 ,format-length-form))
534 `(apply #'modify-or-add-arg
538 ,@(and format-length-form
539 `(:format-length ,format-length-form))
542 (defun format-or-lose (name)
543 (or (gethash name *disassem-inst-formats*)
544 (pd-error "unknown instruction format ~S" name)))
546 ;;; FIXME: needed only at build-the-system time, not in running system
547 (defmacro define-instruction-format (header &rest fields)
549 "DEFINE-INSTRUCTION-FORMAT (Name Length {Format-Key Value}*) Arg-Def*
550 Define an instruction format NAME for the disassembler's use. LENGTH is
551 the length of the format in bits.
552 Possible FORMAT-KEYs:
554 :INCLUDE other-format-name
555 Inherit all arguments and properties of the given format. Any
556 arguments defined in the current format definition will either modify
557 the copy of an existing argument (keeping in the same order with
558 respect to when pre-filter's are called), if it has the same name as
559 one, or be added to the end.
560 :DEFAULT-PRINTER printer-list
561 Use the given PRINTER-LIST as a format to print any instructions of
562 this format when they don't specify something else.
564 Each ARG-DEF defines one argument in the format, and is of the form
565 (Arg-Name {Arg-Key Value}*)
567 Possible ARG-KEYs (the values are evaluated unless otherwise specified):
569 :FIELDS byte-spec-list
570 The argument takes values from these fields in the instruction. If
571 the list is of length one, then the corresponding value is supplied by
572 itself; otherwise it is a list of the values. The list may be NIL.
574 The same as :FIELDS (list byte-spec).
577 If the argument only has one field, this is the value it should have,
578 otherwise it's a list of the values of the individual fields. This can
579 be overridden in an instruction-definition or a format definition
580 including this one by specifying another, or NIL to indicate that it's
584 If non-NIL, the raw value of this argument is sign-extended,
585 immediately after being extracted from the instruction (before any
586 prefilters are run, for instance). If the argument has multiple
587 fields, they are all sign-extended.
590 Inherit any properties of the given argument type.
593 A function which is called (along with all other prefilters, in the
594 order that their arguments appear in the instruction-format) before
595 any printing is done, to filter the raw value. Any uses of READ-SUFFIX
596 must be done inside a prefilter.
598 :PRINTER function-string-or-vector
599 A function, string, or vector which is used to print this argument.
602 If non-NIL, the value of this argument is used as an address, and if
603 that address occurs inside the disassembled code, it is replaced by a
604 label. If this is a function, it is called to filter the value."
605 (gen-format-def-form header fields))
607 ;;; FIXME: needed only at build-the-system time, not in running system
608 (defun gen-format-def-form (header descrips &optional (evalp t))
610 "Generate a form to define an instruction format. See
611 DEFINE-INSTRUCTION-FORMAT for more info."
613 (setf header (list header)))
614 (destructuring-bind (name length &key default-printer include) header
615 (let ((args-var (gensym))
616 (length-var (gensym))
617 (all-wrapper-defs nil)
619 (collect ((arg-def-forms))
620 (dolist (descrip descrips)
621 (let ((name (pop descrip)))
622 (multiple-value-bind (descrip wrapper-defs)
624 descrip evalp t (format nil "~:@(~A~)-~D" name arg-count))
626 (update-args-form args-var `',name descrip evalp length-var))
627 (setf all-wrapper-defs
628 (nconc wrapper-defs all-wrapper-defs)))
632 (eval-when (:compile-toplevel :execute)
633 (let ((,length-var ,length)
638 (format-or-lose ,include))))))
640 (setf (gethash ',name *disassem-inst-formats*)
641 (make-instruction-format
643 :length (bits-to-bytes ,length-var)
644 :default-printer ,(maybe-quote evalp default-printer)
648 ,@(mapcar (lambda (arg)
649 (when (arg-fields arg)
650 (gen-arg-access-macro-def-form
651 arg ,args-var ',name)))
654 ;;; FIXME: probably needed only at build-the-system time, not in
655 ;;; final target system
656 (defun modify-or-add-arg (arg-name
662 (prefilter nil prefilter-p)
663 (printer nil printer-p)
664 (sign-extend nil sign-extend-p)
665 (use-label nil use-label-p)
667 (fields nil fields-p)
669 (let* ((arg-pos (position arg-name args :key #'arg-name))
672 (let ((arg (make-arg :name arg-name)))
674 (setf args (list arg))
675 (push arg (cdr (last args))))
677 (setf (nth arg-pos args)
678 (copy-structure (nth arg-pos args))))))
679 (when (and field-p (not fields-p))
680 (setf fields (list field))
683 (set-arg-from-type arg type type-table))
685 (setf (arg-value arg) value))
687 (setf (arg-prefilter arg) prefilter))
689 (setf (arg-sign-extend-p arg) sign-extend))
691 (setf (arg-printer arg) printer))
693 (setf (arg-use-label arg) use-label))
695 (when (null format-length)
697 "~@<in arg ~S: ~3I~:_~
698 can't specify fields except using DEFINE-INSTRUCTION-FORMAT~:>"
700 (setf (arg-fields arg)
701 (mapcar (lambda (bytespec)
702 (when (> (+ (byte-position bytespec)
703 (byte-size bytespec))
705 (error "~@<in arg ~S: ~3I~:_~
706 The field ~S doesn't fit in an ~
707 instruction-format ~W bits wide.~:>"
711 (correct-dchunk-bytespec-for-endianness
714 sb!c:*backend-byte-order*))
718 (defun gen-arg-access-macro-def-form (arg args format-name)
719 (let* ((funstate (make-funstate args))
720 (arg-val-form (arg-value-form arg funstate :adjusted))
721 (bindings (make-arg-temp-bindings funstate)))
722 `(sb!xc:defmacro ,(symbolicate format-name "-" (arg-name arg))
724 `(let ((chunk ,chunk) (dstate ,dstate))
725 (declare (ignorable chunk dstate))
726 (flet ((local-filtered-value (offset)
727 (declare (type filtered-value-index offset))
728 (aref (dstate-filtered-values dstate) offset))
729 (local-extract (bytespec)
730 (dchunk-extract chunk bytespec)))
731 (declare (ignorable #'local-filtered-value #'local-extract)
732 (inline local-filtered-value local-extract))
734 ,',arg-val-form))))))
736 (defun arg-value-form (arg funstate
739 (allow-multiple-p (not (eq kind :numeric))))
740 (let ((forms (gen-arg-forms arg kind funstate)))
741 (when (and (not allow-multiple-p)
743 (/= (length forms) 1))
744 (pd-error "~S must not have multiple values." arg))
745 (maybe-listify forms)))
747 (defun correct-dchunk-bytespec-for-endianness (bs unit-bits byte-order)
748 (if (eq byte-order :big-endian)
749 (byte (byte-size bs) (+ (byte-position bs) (- dchunk-bits unit-bits)))
752 (defun make-arg-temp-bindings (funstate)
753 ;; (Everything is in reverse order, so we just use PUSH, which
754 ;; results in everything being in the right order at the end.)
755 (let ((bindings nil))
756 (dolist (ats (funstate-arg-temps funstate))
757 (dolist (atk (cdr ats))
758 (cond ((null (cadr atk)))
760 (push `(,(cadr atk) ,(cddr atk)) bindings))
762 (mapc (lambda (var form)
763 (push `(,var ,form) bindings))
768 (defun gen-arg-forms (arg kind funstate)
769 (multiple-value-bind (vars forms)
770 (get-arg-temp arg kind funstate)
772 (multiple-value-bind (new-forms single-value-p)
773 (funcall (find-arg-form-producer kind) arg funstate)
774 (setq forms new-forms)
775 (cond ((or single-value-p (atom forms))
776 (unless (symbolp forms)
777 (setq vars (gensym))))
778 ((every #'symbolp forms)
779 ;; just use the same as the forms
782 (setq vars (make-gensym-list (length forms)))))
783 (set-arg-temps vars forms arg kind funstate)))
786 (defun maybe-listify (forms)
789 ((/= (length forms) 1)
794 (defun set-arg-from-type (arg type-name table)
795 (let ((type-arg (find type-name table :key #'arg-name)))
796 (when (null type-arg)
797 (pd-error "unknown argument type: ~S" type-name))
798 (setf (arg-printer arg) (arg-printer type-arg))
799 (setf (arg-prefilter arg) (arg-prefilter type-arg))
800 (setf (arg-sign-extend-p arg) (arg-sign-extend-p type-arg))
801 (setf (arg-use-label arg) (arg-use-label type-arg))))
803 (defun get-arg-temp (arg kind funstate)
804 (let ((this-arg-temps (assoc arg (funstate-arg-temps funstate))))
806 (let ((this-kind-temps
807 (assoc (canonicalize-arg-form-kind kind)
808 (cdr this-arg-temps))))
809 (values (cadr this-kind-temps) (cddr this-kind-temps)))
812 (defun set-arg-temps (vars forms arg kind funstate)
813 (let ((this-arg-temps
814 (or (assoc arg (funstate-arg-temps funstate))
815 (car (push (cons arg nil) (funstate-arg-temps funstate)))))
816 (kind (canonicalize-arg-form-kind kind)))
817 (let ((this-kind-temps
818 (or (assoc kind (cdr this-arg-temps))
819 (car (push (cons kind nil) (cdr this-arg-temps))))))
820 (setf (cdr this-kind-temps) (cons vars forms)))))
822 ;;; DEFINE-ARG-TYPE Name {Key Value}*
824 ;;; Define a disassembler argument type NAME (which can then be referenced in
825 ;;; another argument definition using the :TYPE argument). &KEY args are:
827 ;;; :SIGN-EXTEND boolean
828 ;;; If non-NIL, the raw value of this argument is sign-extended.
830 ;;; :TYPE arg-type-name
831 ;;; Inherit any properties of given arg-type.
833 ;;; :PREFILTER function
834 ;;; A function which is called (along with all other prefilters,
835 ;;; in the order that their arguments appear in the instruction-
836 ;;; format) before any printing is done, to filter the raw value.
837 ;;; Any uses of READ-SUFFIX must be done inside a prefilter.
839 ;;; :PRINTER function-string-or-vector
840 ;;; A function, string, or vector which is used to print an argument of
844 ;;; If non-NIL, the value of an argument of this type is used as
845 ;;; an address, and if that address occurs inside the disassembled
846 ;;; code, it is replaced by a label. If this is a function, it is
847 ;;; called to filter the value.
848 (defmacro define-arg-type (name &rest args)
849 (gen-arg-type-def-form name args))
851 ;;; Generate a form to define a disassembler argument type. See
852 ;;; DEFINE-ARG-TYPE for more information.
853 (defun gen-arg-type-def-form (name args &optional (evalp t))
854 (multiple-value-bind (args wrapper-defs)
855 (munge-fun-refs args evalp t name)
858 (eval-when (:compile-toplevel :execute)
859 ,(update-args-form '*disassem-arg-types* `',name args evalp))
862 (defmacro def-arg-form-kind ((&rest names) &rest inits)
863 `(let ((kind (make-arg-form-kind :names ',names ,@inits)))
864 ,@(mapcar (lambda (name)
865 `(setf (getf *arg-form-kinds* ',name) kind))
868 (def-arg-form-kind (:raw)
869 :producer (lambda (arg funstate)
870 (declare (ignore funstate))
871 (mapcar (lambda (bytespec)
872 `(the (unsigned-byte ,(byte-size bytespec))
873 (local-extract ',bytespec)))
875 :checker (lambda (new-arg old-arg)
876 (equal (arg-fields new-arg)
877 (arg-fields old-arg))))
879 (def-arg-form-kind (:sign-extended :unfiltered)
880 :producer (lambda (arg funstate)
881 (let ((raw-forms (gen-arg-forms arg :raw funstate)))
882 (if (and (arg-sign-extend-p arg) (listp raw-forms))
883 (mapcar (lambda (form field)
884 `(the (signed-byte ,(byte-size field))
886 ,(byte-size field))))
890 :checker (lambda (new-arg old-arg)
891 (equal (arg-sign-extend-p new-arg)
892 (arg-sign-extend-p old-arg))))
894 (defun valsrc-equal (f1 f2)
897 (equal (value-or-source f1)
898 (value-or-source f2))))
900 (def-arg-form-kind (:filtering)
901 :producer (lambda (arg funstate)
902 (let ((sign-extended-forms
903 (gen-arg-forms arg :sign-extended funstate))
904 (pf (arg-prefilter arg)))
907 `(local-filter ,(maybe-listify sign-extended-forms)
910 (values sign-extended-forms nil))))
911 :checker (lambda (new-arg old-arg)
912 (valsrc-equal (arg-prefilter new-arg) (arg-prefilter old-arg))))
914 (def-arg-form-kind (:filtered :unadjusted)
915 :producer (lambda (arg funstate)
916 (let ((pf (arg-prefilter arg)))
918 (values `(local-filtered-value ,(arg-position arg)) t)
919 (gen-arg-forms arg :sign-extended funstate))))
920 :checker (lambda (new-arg old-arg)
921 (let ((pf1 (arg-prefilter new-arg))
922 (pf2 (arg-prefilter old-arg)))
925 (= (arg-position new-arg)
926 (arg-position old-arg))))))
928 (def-arg-form-kind (:adjusted :numeric :unlabelled)
929 :producer (lambda (arg funstate)
930 (let ((filtered-forms (gen-arg-forms arg :filtered funstate))
931 (use-label (arg-use-label arg)))
932 (if (and use-label (not (eq use-label t)))
934 `(adjust-label ,(maybe-listify filtered-forms)
935 ,(source-form use-label)))
937 :checker (lambda (new-arg old-arg)
938 (valsrc-equal (arg-use-label new-arg) (arg-use-label old-arg))))
940 (def-arg-form-kind (:labelled :final)
941 :producer (lambda (arg funstate)
942 (let ((adjusted-forms
943 (gen-arg-forms arg :adjusted funstate))
944 (use-label (arg-use-label arg)))
946 (let ((form (maybe-listify adjusted-forms)))
947 (if (and (not (eq use-label t))
948 (not (atom adjusted-forms))
949 (/= (Length adjusted-forms) 1))
951 "cannot label a multiple-field argument ~
952 unless using a function: ~S" arg)
953 `((lookup-label ,form))))
955 :checker (lambda (new-arg old-arg)
956 (let ((lf1 (arg-use-label new-arg))
957 (lf2 (arg-use-label old-arg)))
958 (if (null lf1) (null lf2) t))))
960 ;;; This is a bogus kind that's just used to ensure that printers are
962 (def-arg-form-kind (:printed)
963 :producer (lambda (&rest noise)
964 (declare (ignore noise))
965 (pd-error "bogus! can't use the :printed value of an arg!"))
966 :checker (lambda (new-arg old-arg)
967 (valsrc-equal (arg-printer new-arg) (arg-printer old-arg))))
969 (defun remember-printer-use (arg funstate)
970 (set-arg-temps nil nil arg :printed funstate))
972 ;;; Returns a version of THING suitable for including in an evaluable
973 ;;; position in some form.
974 (defun source-form (thing)
975 (cond ((valsrc-p thing)
976 (valsrc-source thing))
979 "can't dump functions, so function ref form must be quoted: ~S"
981 ((self-evaluating-p thing)
983 ((eq (car thing) 'function)
988 ;;; Return anything but a VALSRC structure.
989 (defun value-or-source (thing)
994 (defstruct (cached-fun (:conc-name cached-fun-)
996 (funstate nil :type (or null funstate))
997 (constraint nil :type list)
998 (name nil :type (or null symbol)))
1000 (defun find-cached-fun (cached-funs args constraint)
1001 (dolist (cached-fun cached-funs nil)
1002 (let ((funstate (cached-fun-funstate cached-fun)))
1003 (when (and (equal constraint (cached-fun-constraint cached-fun))
1005 (funstate-compatible-p funstate args)))
1006 (return cached-fun)))))
1008 (defmacro !with-cached-fun ((name-var
1015 (stem (missing-arg)))
1016 &body defun-maker-forms)
1017 (let ((cache-var (gensym))
1018 (constraint-var (gensym)))
1019 `(let* ((,constraint-var ,constraint)
1020 (,cache-var (find-cached-fun (,cache-slot ,cache)
1021 ,args ,constraint-var)))
1023 (values (cached-fun-name ,cache-var) nil))
1025 (let* ((,name-var (symbolicate "CACHED-FUN--" ,stem))
1026 (,funstate-var (make-funstate ,args))
1028 (make-cached-fun :name ,name-var
1029 :funstate ,funstate-var
1030 :constraint ,constraint-var)))
1033 ,(progn ,@defun-maker-forms)
1034 (eval-when (:compile-toplevel :execute)
1036 (,',cache-slot ',,cache)))))))))))
1038 (defun find-printer-fun (%name %format-name printer-source args cache)
1039 (declare (type (or string symbol) %name))
1040 (if (null printer-source)
1042 (let ((printer-source (preprocess-printer printer-source args)))
1044 (name funstate cache fun-cache-printers args
1045 :constraint printer-source
1046 :stem (concatenate 'string
1049 (symbol-name %format-name)
1051 (make-printer-defun printer-source funstate name)))))
1053 (defun make-printer-defun (source funstate fun-name)
1054 (let ((printer-form (compile-printer-list source funstate))
1055 (bindings (make-arg-temp-bindings funstate)))
1056 `(defun ,fun-name (chunk inst stream dstate)
1057 (declare (type dchunk chunk)
1058 (type instruction inst)
1059 (type stream stream)
1060 (type disassem-state dstate))
1061 (macrolet ((local-format-arg (arg fmt)
1062 `(funcall (formatter ,fmt) stream ,arg)))
1063 (flet ((local-tab-to-arg-column ()
1064 (tab (dstate-argument-column dstate) stream))
1065 (local-print-name ()
1066 (princ (inst-print-name inst) stream))
1067 (local-write-char (ch)
1068 (write-char ch stream))
1069 (local-princ (thing)
1070 (princ thing stream))
1071 (local-princ16 (thing)
1072 (princ16 thing stream))
1073 (local-call-arg-printer (arg printer)
1074 (funcall printer arg stream dstate))
1075 (local-call-global-printer (fun)
1076 (funcall fun chunk inst stream dstate))
1077 (local-filtered-value (offset)
1078 (declare (type filtered-value-index offset))
1079 (aref (dstate-filtered-values dstate) offset))
1080 (local-extract (bytespec)
1081 (dchunk-extract chunk bytespec))
1083 (or (gethash lab (dstate-label-hash dstate))
1085 (adjust-label (val adjust-fun)
1086 (funcall adjust-fun val dstate)))
1087 (declare (ignorable #'local-tab-to-arg-column
1089 #'local-princ #'local-princ16
1091 #'local-call-arg-printer
1092 #'local-call-global-printer
1094 #'local-filtered-value
1095 #'lookup-label #'adjust-label)
1096 (inline local-tab-to-arg-column
1097 local-princ local-princ16
1098 local-call-arg-printer local-call-global-printer
1099 local-filtered-value local-extract
1100 lookup-label adjust-label))
1102 ,@printer-form))))))
1104 (defun preprocess-test (subj form args)
1105 (multiple-value-bind (subj test)
1106 (if (and (consp form) (symbolp (car form)) (not (keywordp (car form))))
1107 (values (car form) (cdr form))
1109 (let ((key (if (consp test) (car test) test))
1110 (body (if (consp test) (cdr test) nil)))
1114 ;; If no supplied constant values, just any constant is ok,
1115 ;; just see whether there's some constant value in the arg.
1119 (or (find subj args :key #'arg-name)
1120 (pd-error "unknown argument ~S" subj)))))
1121 ;; Otherwise, defer to run-time.
1132 (preprocess-test subj sub-test args))
1136 (defun preprocess-conditionals (printer args)
1141 (preprocess-conditionals
1142 `(:cond ((:not ,(nth 1 printer)) ,@(nthcdr 2 printer)))
1145 (preprocess-conditionals `(:cond (,(cdr printer))) args))
1147 (preprocess-conditionals
1148 `(:cond (,(nth 1 printer) ,(nth 2 printer))
1149 (t ,(nth 3 printer)))
1157 (let ((filtered-body
1159 (lambda (sub-printer)
1160 (preprocess-conditionals sub-printer args))
1164 (preprocess-test (find-first-field-name filtered-body)
1172 (lambda (sub-printer)
1173 (preprocess-conditionals sub-printer args))
1176 ;;; Return a version of the disassembly-template PRINTER with
1177 ;;; compile-time tests (e.g. :constant without a value), and any
1178 ;;; :CHOOSE operators resolved properly for the args ARGS.
1180 ;;; (:CHOOSE Sub*) simply returns the first Sub in which every field
1181 ;;; reference refers to a valid arg.
1182 (defun preprocess-printer (printer args)
1183 (preprocess-conditionals (preprocess-chooses printer args) args))
1185 ;;; Return the first non-keyword symbol in a depth-first search of TREE.
1186 (defun find-first-field-name (tree)
1189 ((and (symbolp tree) (not (keywordp tree)))
1193 ((eq (car tree) 'quote)
1196 (or (find-first-field-name (car tree))
1197 (find-first-field-name (cdr tree))))))
1199 (defun preprocess-chooses (printer args)
1200 (cond ((atom printer)
1202 ((eq (car printer) :choose)
1203 (pick-printer-choice (cdr printer) args))
1205 (sharing-mapcar (lambda (sub) (preprocess-chooses sub args))
1208 ;;;; some simple functions that help avoid consing when we're just
1209 ;;;; recursively filtering things that usually don't change
1211 (defun sharing-cons (old-cons car cdr)
1213 "If CAR is eq to the car of OLD-CONS and CDR is eq to the CDR, return
1214 OLD-CONS, otherwise return (cons CAR CDR)."
1215 (if (and (eq car (car old-cons)) (eq cdr (cdr old-cons)))
1219 (defun sharing-mapcar (fun list)
1220 (declare (type function fun))
1222 "A simple (one list arg) mapcar that avoids consing up a new list
1223 as long as the results of calling FUN on the elements of LIST are
1224 eq to the original."
1227 (funcall fun (car list))
1228 (sharing-mapcar fun (cdr list)))))
1230 (defun all-arg-refs-relevant-p (printer args)
1231 (cond ((or (null printer) (keywordp printer) (eq printer t))
1234 (find printer args :key #'arg-name))
1236 (every (lambda (x) (all-arg-refs-relevant-p x args))
1240 (defun pick-printer-choice (choices args)
1241 (dolist (choice choices
1242 (pd-error "no suitable choice found in ~S" choices))
1243 (when (all-arg-refs-relevant-p choice args)
1246 (defun compile-printer-list (sources funstate)
1247 (unless (null sources)
1248 ;; Coalesce adjacent symbols/strings, and convert to strings if possible,
1249 ;; since they require less consing to write.
1250 (do ((el (car sources) (car sources))
1251 (names nil (cons (strip-quote el) names)))
1252 ((not (string-or-qsym-p el))
1254 ;; concatenate adjacent strings and symbols
1256 (apply #'concatenate
1258 (mapcar #'string (nreverse names)))))
1259 (push (if (some #'alpha-char-p string)
1260 `',(make-symbol string) ; Preserve casifying output.
1264 (cons (compile-printer-body (car sources) funstate)
1265 (compile-printer-list (cdr sources) funstate))))
1267 (defun compile-printer-body (source funstate)
1268 (cond ((null source)
1271 `(local-print-name))
1273 `(local-tab-to-arg-column))
1275 (pd-error "unknown printer element: ~S" source))
1277 (compile-print source funstate))
1279 `(local-princ ',source))
1280 ((eq (car source) :using)
1281 (unless (or (stringp (cadr source))
1282 (and (listp (cadr source))
1283 (eq (caadr source) 'function)))
1284 (pd-error "The first arg to :USING must be a string or #'function."))
1285 (compile-print (caddr source) funstate
1286 (cons (eval (cadr source)) (cadr source))))
1287 ((eq (car source) :plus-integer)
1288 ;; prints the given field proceed with a + or a -
1290 (arg-value-form (arg-or-lose (cadr source) funstate)
1295 (local-write-char #\+))
1296 (local-princ ,form))))
1297 ((eq (car source) 'quote)
1298 `(local-princ ,source))
1299 ((eq (car source) 'function)
1300 `(local-call-global-printer ,source))
1301 ((eq (car source) :cond)
1302 `(cond ,@(mapcar (lambda (clause)
1303 `(,(compile-test (find-first-field-name
1307 ,@(compile-printer-list (cdr clause)
1310 ;; :IF, :UNLESS, and :WHEN are replaced by :COND during preprocessing
1312 `(progn ,@(compile-printer-list source funstate)))))
1314 (defun compile-print (arg-name funstate &optional printer)
1315 (let* ((arg (arg-or-lose arg-name funstate))
1316 (printer (or printer (arg-printer arg)))
1317 (printer-val (value-or-source printer))
1318 (printer-src (source-form printer)))
1319 (remember-printer-use arg funstate)
1320 (cond ((stringp printer-val)
1321 `(local-format-arg ,(arg-value-form arg funstate) ,printer-val))
1322 ((vectorp printer-val)
1325 ,(arg-value-form arg funstate :numeric))))
1326 ((or (functionp printer-val)
1327 (and (consp printer-val) (eq (car printer-val) 'function)))
1328 `(local-call-arg-printer ,(arg-value-form arg funstate)
1330 ((or (null printer-val) (eq printer-val t))
1331 `(,(if (arg-use-label arg) 'local-princ16 'local-princ)
1332 ,(arg-value-form arg funstate)))
1334 (pd-error "illegal printer: ~S" printer-src)))))
1336 (defun string-or-qsym-p (thing)
1339 (eq (car thing) 'quote)
1340 (or (stringp (cadr thing))
1341 (symbolp (cadr thing))))))
1343 (defun strip-quote (thing)
1344 (if (and (consp thing) (eq (car thing) 'quote))
1348 (defun compare-fields-form (val-form-1 val-form-2)
1349 (flet ((listify-fields (fields)
1350 (cond ((symbolp fields) fields)
1351 ((every #'constantp fields) `',fields)
1352 (t `(list ,@fields)))))
1353 (cond ((or (symbolp val-form-1) (symbolp val-form-2))
1354 `(equal ,(listify-fields val-form-1)
1355 ,(listify-fields val-form-2)))
1357 `(and ,@(mapcar (lambda (v1 v2) `(= ,v1 ,v2))
1358 val-form-1 val-form-2))))))
1360 (defun compile-test (subj test funstate)
1361 (when (and (consp test) (symbolp (car test)) (not (keywordp (car test))))
1362 (setf subj (car test)
1364 (let ((key (if (consp test) (car test) test))
1365 (body (if (consp test) (cdr test) nil)))
1371 (let* ((arg (arg-or-lose subj funstate))
1372 (fields (arg-fields arg))
1374 (when (not (= (length fields) (length consts)))
1375 (pd-error "The number of constants doesn't match number of ~
1376 fields in: (~S :constant~{ ~S~})"
1378 (compare-fields-form (gen-arg-forms arg :numeric funstate)
1381 `(> ,(arg-value-form (arg-or-lose subj funstate) funstate :numeric)
1384 `(< ,(arg-value-form (arg-or-lose subj funstate) funstate :numeric)
1387 (let ((arg1 (arg-or-lose subj funstate))
1388 (arg2 (arg-or-lose (car body) funstate)))
1389 (unless (and (= (length (arg-fields arg1))
1390 (length (arg-fields arg2)))
1391 (every (lambda (bs1 bs2)
1392 (= (byte-size bs1) (byte-size bs2)))
1395 (pd-error "can't compare differently sized fields: ~
1396 (~S :same-as ~S)" subj (car body)))
1397 (compare-fields-form (gen-arg-forms arg1 :numeric funstate)
1398 (gen-arg-forms arg2 :numeric funstate))))
1400 `(or ,@(mapcar (lambda (sub) (compile-test subj sub funstate))
1403 `(and ,@(mapcar (lambda (sub) (compile-test subj sub funstate))
1406 `(not ,(compile-test subj (car body) funstate)))
1407 ((and (consp key) (null body))
1408 (compile-test subj key funstate))
1410 (pd-error "bogus test-form: ~S" test)))))
1412 (defun find-labeller-fun (%name args cache)
1413 (let ((labelled-fields
1414 (mapcar #'arg-name (remove-if-not #'arg-use-label args))))
1415 (if (null labelled-fields)
1418 (name funstate cache fun-cache-labellers args
1419 :stem (concatenate 'string "LABELLER-" (string %name))
1420 :constraint labelled-fields)
1421 (let ((labels-form 'labels))
1423 (when (arg-use-label arg)
1425 `(let ((labels ,labels-form)
1427 ,(arg-value-form arg funstate :adjusted nil)))
1428 (if (assoc addr labels :test #'eq)
1430 (cons (cons addr nil) labels))))))
1431 `(defun ,name (chunk labels dstate)
1432 (declare (type list labels)
1434 (type disassem-state dstate))
1435 (flet ((local-filtered-value (offset)
1436 (declare (type filtered-value-index offset))
1437 (aref (dstate-filtered-values dstate) offset))
1438 (local-extract (bytespec)
1439 (dchunk-extract chunk bytespec))
1440 (adjust-label (val adjust-fun)
1441 (funcall adjust-fun val dstate)))
1442 (declare (ignorable #'local-filtered-value #'local-extract
1444 (inline local-filtered-value local-extract
1446 (let* ,(make-arg-temp-bindings funstate)
1447 ,labels-form))))))))
1449 (defun find-prefilter-fun (%name %format-name args cache)
1450 (declare (type (or symbol string) %name %format-name))
1451 (let ((filtered-args (mapcar #'arg-name
1452 (remove-if-not #'arg-prefilter args))))
1453 (if (null filtered-args)
1456 (name funstate cache fun-cache-prefilters args
1457 :stem (concatenate 'string
1460 (string %format-name)
1462 :constraint filtered-args)
1465 (let ((pf (arg-prefilter arg)))
1468 `(setf (local-filtered-value ,(arg-position arg))
1470 (gen-arg-forms arg :filtering funstate)))))
1472 `(defun ,name (chunk dstate)
1473 (declare (type dchunk chunk)
1474 (type disassem-state dstate))
1475 (flet (((setf local-filtered-value) (value offset)
1476 (declare (type filtered-value-index offset))
1477 (setf (aref (dstate-filtered-values dstate) offset)
1479 (local-filter (value filter)
1480 (funcall filter value dstate))
1481 (local-extract (bytespec)
1482 (dchunk-extract chunk bytespec)))
1483 (declare (ignorable #'local-filter #'local-extract)
1484 (inline (setf local-filtered-value)
1485 local-filter local-extract))
1486 ;; Use them for side effects only.
1487 (let* ,(make-arg-temp-bindings funstate)
1490 (defun compute-mask-id (args)
1491 (let ((mask dchunk-zero)
1493 (dolist (arg args (values mask id))
1494 (let ((av (arg-value arg)))
1496 (do ((fields (arg-fields arg) (cdr fields))
1497 (values (if (atom av) (list av) av) (cdr values)))
1499 (let ((field-mask (dchunk-make-mask (car fields))))
1500 (when (/= (dchunk-and mask field-mask) dchunk-zero)
1501 (pd-error "The field ~S in arg ~S overlaps some other field."
1504 (dchunk-insertf id (car fields) (car values))
1505 (dchunk-orf mask field-mask))))))))
1507 (defun install-inst-flavors (name flavors)
1508 (setf (gethash name *disassem-insts*)
1511 #!-sb-fluid (declaim (inline bytes-to-bits))
1512 (declaim (maybe-inline sign-extend aligned-p align tab tab0))
1514 (defun bytes-to-bits (bytes)
1515 (declare (type length bytes))
1516 (* bytes sb!vm:n-byte-bits))
1518 (defun bits-to-bytes (bits)
1519 (declare (type length bits))
1520 (multiple-value-bind (bytes rbits)
1521 (truncate bits sb!vm:n-byte-bits)
1522 (when (not (zerop rbits))
1523 (error "~W bits is not a byte-multiple." bits))
1526 (defun sign-extend (int size)
1527 (declare (type integer int)
1528 (type (integer 0 128) size))
1529 (if (logbitp (1- size) int)
1530 (dpb int (byte size 0) -1)
1533 ;;; Is ADDRESS aligned on a SIZE byte boundary?
1534 (defun aligned-p (address size)
1535 (declare (type address address)
1536 (type alignment size))
1537 (zerop (logand (1- size) address)))
1539 ;;; Return ADDRESS aligned *upward* to a SIZE byte boundary.
1540 (defun align (address size)
1541 (declare (type address address)
1542 (type alignment size))
1543 (logandc1 (1- size) (+ (1- size) address)))
1545 (defun tab (column stream)
1546 (funcall (formatter "~V,1t") stream column)
1548 (defun tab0 (column stream)
1549 (funcall (formatter "~V,0t") stream column)
1552 (defun princ16 (value stream)
1553 (write value :stream stream :radix t :base 16 :escape nil))
1555 (defun read-signed-suffix (length dstate)
1556 (declare (type (member 8 16 32) length)
1557 (type disassem-state dstate)
1558 (optimize (speed 3) (safety 0)))
1559 (sign-extend (read-suffix length dstate) length))
1561 ;;; All state during disassembly. We store some seemingly redundant
1562 ;;; information so that we can allow garbage collect during disassembly and
1563 ;;; not get tripped up by a code block being moved...
1564 (defstruct (disassem-state (:conc-name dstate-)
1565 (:constructor %make-dstate)
1567 ;; offset of current pos in segment
1568 (cur-offs 0 :type offset)
1569 ;; offset of next position
1570 (next-offs 0 :type offset)
1571 ;; a sap pointing to our segment
1572 (segment-sap (missing-arg) :type sb!sys:system-area-pointer)
1573 ;; the current segment
1574 (segment nil :type (or null segment))
1575 ;; what to align to in most cases
1576 (alignment sb!vm:n-word-bytes :type alignment)
1577 (byte-order :little-endian
1578 :type (member :big-endian :little-endian))
1579 ;; for user code to hang stuff off of
1580 (properties nil :type list)
1581 (filtered-values (make-array max-filtered-value-index)
1582 :type filtered-value-vector)
1583 ;; used for prettifying printing
1584 (addr-print-len nil :type (or null (integer 0 20)))
1585 (argument-column 0 :type column)
1586 ;; to make output look nicer
1587 (output-state :beginning
1588 :type (member :beginning
1592 ;; alist of (address . label-number)
1593 (labels nil :type list)
1594 ;; same as LABELS slot data, but in a different form
1595 (label-hash (make-hash-table) :type hash-table)
1597 (fun-hooks nil :type list)
1599 ;; alist of (address . label-number), popped as it's used
1600 (cur-labels nil :type list)
1601 ;; OFFS-HOOKs, popped as they're used
1602 (cur-offs-hooks nil :type list)
1604 ;; for the current location
1605 (notes nil :type list)
1607 ;; currently active source variables
1608 (current-valid-locations nil :type (or null (vector bit))))
1609 (def!method print-object ((dstate disassem-state) stream)
1610 (print-unreadable-object (dstate stream :type t)
1613 (dstate-cur-offs dstate)
1614 (dstate-segment dstate))))
1616 ;;; Return the absolute address of the current instruction in DSTATE.
1617 (defun dstate-cur-addr (dstate)
1618 (the address (+ (seg-virtual-location (dstate-segment dstate))
1619 (dstate-cur-offs dstate))))
1621 ;;; Return the absolute address of the next instruction in DSTATE.
1622 (defun dstate-next-addr (dstate)
1623 (the address (+ (seg-virtual-location (dstate-segment dstate))
1624 (dstate-next-offs dstate))))
1626 ;;; Get the value of the property called NAME in DSTATE. Also SETF'able.
1628 ;;; KLUDGE: The associated run-time machinery for this is in
1629 ;;; target-disassem.lisp (much later). This is here just to make sure
1630 ;;; it's defined before it's used. -- WHN ca. 19990701
1631 (defmacro dstate-get-prop (dstate name)
1632 `(getf (dstate-properties ,dstate) ,name))