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 (defconstant 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 #.sb
!vm
:n-word-bits
))
22 (deftype disassem-length
() '(unsigned-byte 24))
23 (deftype column
() '(integer 0 1000))
25 (defconstant 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
33 ;; With a few tweaks, you can use a running SBCL as a cross-assembler
34 ;; and disassembler for other supported backends,
35 ;; if that backend has been converted to use a distinct ASM package.
36 (eval-when (:compile-toplevel
:load-toplevel
:execute
)
37 (defparameter sb
!assem
::*backend-instruction-set-package
*
38 (find-package #.
(sb-cold::backend-asm-package-name
))))
40 (defvar *disassem-inst-space
* nil
)
42 ;;; minimum alignment of instructions, in bytes
43 (defvar *disassem-inst-alignment-bytes
* sb
!vm
:n-word-bytes
)
44 (declaim (type alignment
*disassem-inst-alignment-bytes
*))
46 ;; How many columns of output to allow for the address preceding each line.
47 ;; If NIL, use the minimum possible width for the disassembly range.
48 ;; If 0, do not print addresses.
49 (defvar *disassem-location-column-width
* nil
)
50 (declaim (type (or null text-width
) *disassem-location-column-width
*))
52 ;;; the width of the column in which instruction-names are printed. A
53 ;;; value of zero gives the effect of not aligning the arguments at
55 (defvar *disassem-opcode-column-width
* 0)
56 (declaim (type text-width
*disassem-opcode-column-width
*))
58 ;;; the width of the column in which instruction-bytes are printed. A
59 ;;; value of zero disables the printing of instruction bytes.
60 (defvar *disassem-inst-column-width
* 16
62 "The width of instruction bytes.")
63 (declaim (type text-width
*disassem-inst-column-width
*))
65 (defvar *disassem-note-column
* (+ 45 *disassem-inst-column-width
*)
67 "The column in which end-of-line comments for notes are started.")
69 ;;;; A DCHUNK contains the bits we look at to decode an
71 ;;;; I tried to keep this abstract so that if using integers > the machine
72 ;;;; word size conses too much, it can be changed to use bit-vectors or
75 ;;;; KLUDGE: It's not clear that using bit-vectors would be any more efficient.
76 ;;;; Perhaps the abstraction could go away. -- WHN 19991124
79 (declaim (inline dchunk-or dchunk-and dchunk-clear dchunk-not
80 dchunk-make-mask dchunk-make-field
86 (defconstant dchunk-bits sb
!vm
:n-word-bits
)
89 `(unsigned-byte ,dchunk-bits
))
90 (deftype dchunk-index
()
91 `(integer 0 ,dchunk-bits
))
93 (defconstant dchunk-zero
0)
94 (defconstant dchunk-one
(1- (expt 2 sb
!vm
:n-word-bits
)))
96 (defun dchunk-extract (chunk byte-spec
)
97 (declare (type dchunk chunk
))
98 (the dchunk
(ldb byte-spec
(the dchunk chunk
))))
100 (defmacro dchunk-copy
(x)
103 (defun dchunk-or (to from
)
104 (declare (type dchunk to from
))
105 (the dchunk
(logior to from
)))
106 (defun dchunk-and (to from
)
107 (declare (type dchunk to from
))
108 (the dchunk
(logand to from
)))
109 (defun dchunk-clear (to from
)
110 (declare (type dchunk to from
))
111 (the dchunk
(logandc2 to from
)))
112 (defun dchunk-not (from)
113 (declare (type dchunk from
))
114 (the dchunk
(logand dchunk-one
(lognot from
))))
116 (defmacro dchunk-andf
(to from
)
117 `(setf ,to
(dchunk-and ,to
,from
)))
118 (defmacro dchunk-orf
(to from
)
119 `(setf ,to
(dchunk-or ,to
,from
)))
120 (defmacro dchunk-clearf
(to from
)
121 `(setf ,to
(dchunk-clear ,to
,from
)))
123 (defun dchunk-make-mask (pos)
124 (the dchunk
(mask-field pos -
1)))
125 (defun dchunk-make-field (pos value
)
126 (the dchunk
(dpb value pos
0)))
128 (defmacro make-dchunk
(value)
129 `(the dchunk
,value
))
131 #-sb-xc-host
;; FIXME: function belongs in 'target-disassem'
132 (defun sap-ref-dchunk (sap byte-offset byte-order
)
133 (declare (type sb
!sys
:system-area-pointer sap
)
134 (type offset byte-offset
)
135 (muffle-conditions compiler-note
) ; returns possible bignum
136 (optimize (speed 3) (safety 0)))
139 (32 (if (eq byte-order
:big-endian
)
140 (+ (ash (sb!sys
:sap-ref-8 sap byte-offset
) 24)
141 (ash (sb!sys
:sap-ref-8 sap
(+ 1 byte-offset
)) 16)
142 (ash (sb!sys
:sap-ref-8 sap
(+ 2 byte-offset
)) 8)
143 (sb!sys
:sap-ref-8 sap
(+ 3 byte-offset
)))
144 (+ (sb!sys
:sap-ref-8 sap byte-offset
)
145 (ash (sb!sys
:sap-ref-8 sap
(+ 1 byte-offset
)) 8)
146 (ash (sb!sys
:sap-ref-8 sap
(+ 2 byte-offset
)) 16)
147 (ash (sb!sys
:sap-ref-8 sap
(+ 3 byte-offset
)) 24))))
148 (64 (if (eq byte-order
:big-endian
)
149 (+ (ash (sb!sys
:sap-ref-8 sap byte-offset
) 56)
150 (ash (sb!sys
:sap-ref-8 sap
(+ 1 byte-offset
)) 48)
151 (ash (sb!sys
:sap-ref-8 sap
(+ 2 byte-offset
)) 40)
152 (ash (sb!sys
:sap-ref-8 sap
(+ 3 byte-offset
)) 32)
153 (ash (sb!sys
:sap-ref-8 sap
(+ 4 byte-offset
)) 24)
154 (ash (sb!sys
:sap-ref-8 sap
(+ 5 byte-offset
)) 16)
155 (ash (sb!sys
:sap-ref-8 sap
(+ 6 byte-offset
)) 8)
156 (sb!sys
:sap-ref-8 sap
(+ 7 byte-offset
)))
157 (+ (sb!sys
:sap-ref-8 sap byte-offset
)
158 (ash (sb!sys
:sap-ref-8 sap
(+ 1 byte-offset
)) 8)
159 (ash (sb!sys
:sap-ref-8 sap
(+ 2 byte-offset
)) 16)
160 (ash (sb!sys
:sap-ref-8 sap
(+ 3 byte-offset
)) 24)
161 (ash (sb!sys
:sap-ref-8 sap
(+ 4 byte-offset
)) 32)
162 (ash (sb!sys
:sap-ref-8 sap
(+ 5 byte-offset
)) 40)
163 (ash (sb!sys
:sap-ref-8 sap
(+ 6 byte-offset
)) 48)
164 (ash (sb!sys
:sap-ref-8 sap
(+ 7 byte-offset
)) 56)))))))
166 (defun dchunk-corrected-extract (from pos unit-bits byte-order
)
167 (declare (type dchunk from
))
168 (if (eq byte-order
:big-endian
)
169 (ldb (byte (byte-size pos
)
170 (+ (byte-position pos
) (- dchunk-bits unit-bits
)))
172 (ldb pos
(the dchunk from
))))
174 (defmacro dchunk-insertf
(place pos value
)
175 `(setf ,place
(the dchunk
(dpb ,value
,pos
(the dchunk
,place
)))))
178 (declare (type dchunk x y
))
180 (defmacro dchunk-zerop
(x)
181 `(dchunk= ,x dchunk-zero
))
183 (defun dchunk-strict-superset-p (sup sub
)
184 (and (zerop (logandc2 sub sup
))
185 (not (zerop (logandc2 sup sub
)))))
187 (defun dchunk-count-bits (x)
188 (declare (type dchunk x
))
191 (defstruct (instruction (:conc-name inst-
)
193 make-instruction
(name format-name print-name
194 length mask id printer labeller
197 (name nil
:type
(or symbol string
) :read-only t
)
198 (format-name nil
:type
(or symbol string
) :read-only t
)
200 (mask dchunk-zero
:type dchunk
:read-only t
) ; bits in the inst that are constant
201 (id dchunk-zero
:type dchunk
:read-only t
) ; value of those constant bits
203 (length 0 :type disassem-length
:read-only t
) ; in bytes
205 (print-name nil
:type symbol
:read-only t
)
207 ;; disassembly "functions"
208 (prefilters nil
:type list
:read-only t
)
209 (labeller nil
:type
(or list vector
) :read-only t
)
210 (printer nil
:type
(or null function
) :read-only t
)
211 (control nil
:type
(or null function
) :read-only t
)
213 ;; instructions that are the same as this instruction but with more
215 (specializers nil
:type list
))
216 (defmethod print-object ((inst instruction
) stream
)
217 (print-unreadable-object (inst stream
:type t
:identity t
)
218 (format stream
"~A(~A)" (inst-name inst
) (inst-format-name inst
))))
220 ;;;; an instruction space holds all known machine instructions in a
221 ;;;; form that can be easily searched
223 (defstruct (inst-space (:conc-name ispace-
)
225 (valid-mask dchunk-zero
:type dchunk
) ; applies to *children*
226 (choices nil
:type list
))
227 (defmethod print-object ((ispace inst-space
) stream
)
228 (print-unreadable-object (ispace stream
:type t
:identity t
)))
230 ;;; now that we've defined the structure, we can declaim the type of
232 (declaim (type (or null inst-space
) *disassem-inst-space
*))
234 (defstruct (inst-space-choice (:conc-name ischoice-
)
236 (common-id dchunk-zero
:type dchunk
) ; applies to *parent's* mask
237 (subspace (missing-arg) :type
(or inst-space instruction
)))
239 (defmacro !begin-instruction-definitions
() nil
) ; FIXME: remove
241 ;;; FIXME: If we we interned the temp vars,
242 ;;; and wouldn't use symbols qua strings, then this would reduce to EQUAL.
243 (defun equal-mod-gensyms (a b
)
244 (named-let recurse
((a a
) (b b
))
247 (list (and (listp b
) (recurse (car a
) (car b
)) (recurse (cdr a
) (cdr b
))))
250 (not (symbol-package a
))
251 (not (symbol-package b
))
252 ;; If "strings", then comparison by STRING= is right,
253 ;; and if lexical vars, it's also right because
254 ;; we never rebind a given temp within a function.
256 ((or number character function
) (eql a b
))
257 (vector (and (vectorp b
) (every #'recurse a b
))))))
259 (defstruct (arg (:copier nil
)
261 (:constructor %make-arg
(name))
263 (lambda (self stream
)
266 (print-unreadable-object (self stream
:type t
)
268 "~A ~:[~;+~]~:S~@[=~S~]~@[ filt=~S~]~
269 ~@[ lbl=~S~]~@[ prt=~S~]"
271 (arg-sign-extend-p self
)
276 (arg-printer self
)))))))
277 (name nil
:type symbol
)
278 (fields nil
:type list
)
280 (value nil
:type
(or list integer
))
281 (sign-extend-p nil
:type boolean
)
284 (printer nil
:type
(or null function vector
))
285 (prefilter nil
:type
(or null function
))
286 (use-label nil
:type
(or boolean function
)))
288 (defstruct (instruction-format (:conc-name format-
)
289 (:constructor make-inst-format
290 (name length default-printer args
))
293 (args nil
:type list
)
295 (length 0 :type disassem-length
) ; in bytes
297 (default-printer nil
:type list
))
299 ;;; A FUNSTATE holds the state of any arguments used in a disassembly
300 ;;; function. It is a 2-level alist. The outer list maps each ARG to
301 ;;; a list of styles in which that arg can be rendered.
302 ;;; Each rendering is named by a keyword (the key to the inner alist),
303 ;;; and is represented as a list of temp vars and values for them.
304 (defun make-funstate (args) (mapcar #'list args
))
306 (defun arg-position (arg funstate
)
307 ;;; The THE form is to assert that ARG is found.
308 (the filtered-value-index
(position arg funstate
:key
#'car
)))
310 (defun arg-or-lose (name funstate
)
311 (or (car (assoc name funstate
:key
#'arg-name
:test
#'eq
))
312 (pd-error "unknown argument ~S" name
)))
314 ;;; machinery to provide more meaningful error messages during compilation
315 (defvar *current-instruction-flavor
*)
316 (defun pd-error (fmt &rest args
)
317 (if (boundp '*current-instruction-flavor
*)
318 (error "~{A printer ~D~}: ~?" *current-instruction-flavor
* fmt args
)
319 (apply #'error fmt args
)))
321 (defun format-or-lose (name)
322 (or (get name
'inst-format
)
323 (pd-error "unknown instruction format ~S" name
)))
325 ;;; Return a modified copy of ARG that has property values changed
326 ;;; depending on whether it is being used at compile-time or load-time.
327 ;;; This is to avoid evaluating #'FOO references at compile-time
328 ;;; while allowing compile-time manipulation of byte specifiers.
329 (defun massage-arg (spec when
)
332 ;; At compile-time we get a restricted view of the DEFINE-ARG-TYPE args,
333 ;; just enough to macroexpand :READER definitions. :TYPE and ::SIGN-EXTEND
334 ;; are as specified, but :PREFILTER, :LABELLER, and :PRINTER are not
335 ;; compile-time evaluated.
336 (loop for
(indicator val
) on
(cdr spec
) by
#'cddr
337 nconc
(case indicator
338 (:sign-extend
; Only a literal T or NIL is allowed
339 (list indicator
(the boolean val
)))
341 ;; #'ERROR is a placeholder for any compile-time non-nil
342 ;; value. If nil, it must be literally nil, not 'NIL.
343 (list indicator
(if val
#'error nil
)))
344 ((:field
:fields
:type
)
345 (list indicator val
)))))
347 (loop for
(indicator raw-val
) on
(cdr spec
) by
#'cddr
348 ;; Use NAMED-LAMBDAs to enhance debuggability,
349 for val
= (if (typep raw-val
'(cons (eql lambda
)))
350 `(named-lambda ,(format nil
"~A.~A" (car spec
) indicator
)
353 nconc
(case indicator
354 (:reader nil
) ; drop it
355 (:prefilter
; Enforce compile-time-determined not-nullness.
356 (list indicator
(if val
`(the (not null
) ,val
) nil
)))
357 (t (list indicator val
)))))))
359 (defmacro define-instruction-format
((format-name length-in-bits
360 &key default-printer include
)
362 #+sb-xc-host
(declare (ignore default-printer
))
364 "DEFINE-INSTRUCTION-FORMAT (Name Length {Format-Key Value}*) Arg-Def*
365 Define an instruction format NAME for the disassembler's use. LENGTH is
366 the length of the format in bits.
367 Possible FORMAT-KEYs:
369 :INCLUDE other-format-name
370 Inherit all arguments and properties of the given format. Any
371 arguments defined in the current format definition will either modify
372 the copy of an existing argument (keeping in the same order with
373 respect to when prefilters are called), if it has the same name as
374 one, or be added to the end.
375 :DEFAULT-PRINTER printer-list
376 Use the given PRINTER-LIST as a format to print any instructions of
377 this format when they don't specify something else.
379 Each ARG-DEF defines one argument in the format, and is of the form
380 (Arg-Name {Arg-Key Value}*)
382 Possible ARG-KEYs (the values are evaluated unless otherwise specified):
384 :FIELDS byte-spec-list
385 The argument takes values from these fields in the instruction. If
386 the list is of length one, then the corresponding value is supplied by
387 itself; otherwise it is a list of the values. The list may be NIL.
389 The same as :FIELDS (list byte-spec).
392 If the argument only has one field, this is the value it should have,
393 otherwise it's a list of the values of the individual fields. This can
394 be overridden in an instruction-definition or a format definition
395 including this one by specifying another, or NIL to indicate that it's
399 If non-NIL, the raw value of this argument is sign-extended,
400 immediately after being extracted from the instruction (before any
401 prefilters are run, for instance). If the argument has multiple
402 fields, they are all sign-extended.
405 Inherit any properties of the given argument type.
408 A function which is called (along with all other prefilters, in the
409 order that their arguments appear in the instruction-format) before
410 any printing is done, to filter the raw value. Any uses of READ-SUFFIX
411 must be done inside a prefilter.
413 :PRINTER function-string-or-vector
414 A function, string, or vector which is used to print this argument.
417 If non-NIL, the value of this argument is used as an address, and if
418 that address occurs inside the disassembled code, it is replaced by a
419 label. If this is a function, it is called to filter the value."
421 (eval-when (:compile-toplevel
)
423 ',format-name
',include
,length-in-bits nil
424 ,@(mapcar (lambda (arg) `(list ',(car arg
) ,@(massage-arg arg
:compile
)))
428 (awhen (getf (cdr arg-spec
) :reader
)
429 `((defun ,it
(dchunk dstate
)
430 (declare (ignorable dchunk dstate
))
431 (flet ((local-filtered-value (offset)
432 (declare (type filtered-value-index offset
))
433 (aref (dstate-filtered-values dstate
) offset
))
434 (local-extract (bytespec)
435 (dchunk-extract dchunk bytespec
)))
436 (declare (ignorable #'local-filtered-value
#'local-extract
)
437 (inline local-filtered-value local-extract
))
438 ;; Delay ARG-FORM-VALUE call until after compile-time-too
439 ;; processing of !%DEF-INSTRUCTION-FORMAT has happened.
443 (format-args (format-or-lose ',format-name
)))
444 (arg (find ',(car arg-spec
) format-args
446 (funstate (make-funstate format-args
))
447 (expr (arg-value-form arg funstate
:numeric
)))
448 `(let* ,(make-arg-temp-bindings funstate
) ,expr
))))
451 #-sb-xc-host
; Host doesn't need the real definition.
453 ',format-name
',include
,length-in-bits
,default-printer
454 ,@(mapcar (lambda (arg) `(list ',(car arg
) ,@(massage-arg arg
:eval
)))
457 (defun %def-inst-format
(name inherit length printer
&rest arg-specs
)
458 (let ((args (if inherit
(copy-list (format-args (format-or-lose inherit
)))))
460 (dolist (arg-spec arg-specs
)
461 (let* ((arg-name (car arg-spec
))
462 (properties (cdr arg-spec
))
463 (cell (member arg-name args
:key
#'arg-name
)))
464 (aver (not (memq arg-name seen
)))
467 (setq args
(nconc args
(list (apply #'modify-arg
(%make-arg arg-name
)
468 length properties
)))))
470 (rplaca cell
(apply #'modify-arg
(copy-structure (car cell
))
471 length properties
))))))
472 (setf (get name
'inst-format
)
473 (make-inst-format name
(bits-to-bytes length
) printer args
))))
475 (defun modify-arg (arg format-length
476 &key
(value nil value-p
)
478 (prefilter nil prefilter-p
)
479 (printer nil printer-p
)
480 (sign-extend nil sign-extend-p
)
481 (use-label nil use-label-p
)
483 (fields nil fields-p
))
486 (error ":FIELD and :FIELDS are mutually exclusive")
487 (setf fields
(list field
) fields-p t
)))
489 (let ((type-arg (or (get type
'arg-type
)
490 (pd-error "unknown argument type: ~S" type
))))
491 (setf (arg-printer arg
) (arg-printer type-arg
))
492 (setf (arg-prefilter arg
) (arg-prefilter type-arg
))
493 (setf (arg-sign-extend-p arg
) (arg-sign-extend-p type-arg
))
494 (setf (arg-use-label arg
) (arg-use-label type-arg
))))
496 (setf (arg-value arg
) value
))
498 (setf (arg-prefilter arg
) prefilter
))
500 (setf (arg-sign-extend-p arg
) sign-extend
))
502 (setf (arg-printer arg
) printer
))
504 (setf (arg-use-label arg
) use-label
))
506 (setf (arg-fields arg
)
507 (mapcar (lambda (bytespec)
508 (when (> (+ (byte-position bytespec
) (byte-size bytespec
))
510 (error "~@<in arg ~S: ~3I~:_~
511 The field ~S doesn't fit in an ~
512 instruction-format ~W bits wide.~:>"
513 (arg-name arg
) bytespec format-length
))
514 (correct-dchunk-bytespec-for-endianness
515 bytespec format-length sb
!c
:*backend-byte-order
*))
519 (defun arg-value-form (arg funstate
522 (allow-multiple-p (neq rendering
:numeric
)))
523 (let ((forms (gen-arg-forms arg rendering funstate
)))
524 (when (and (not allow-multiple-p
)
526 (/= (length forms
) 1))
527 (pd-error "~S must not have multiple values." arg
))
528 (maybe-listify forms
)))
530 (defun correct-dchunk-bytespec-for-endianness (bs unit-bits byte-order
)
531 (if (eq byte-order
:big-endian
)
532 (byte (byte-size bs
) (+ (byte-position bs
) (- dchunk-bits unit-bits
)))
535 (defun make-arg-temp-bindings (funstate)
536 (let ((bindings nil
))
537 ;; Prefilters have to be called in the correct order, so reverse FUNSTATE
538 ;; because we're using PUSH in the inner loop.
539 (dolist (arg-cell (reverse funstate
) bindings
)
540 ;; These sublists are "backwards", so PUSH ends up being correct.
541 (dolist (rendering (cdr arg-cell
))
542 (let* ((binding (cdr rendering
))
544 (vals (cdr binding
)))
546 (mapc (lambda (var val
) (push `(,var
,val
) bindings
)) vars vals
)
547 (push `(,vars
,vals
) bindings
)))))))
549 ;;; Return the form(s) that should be evaluated to render ARG in the chosen
550 ;;; RENDERING style, which is one of :RAW, :SIGN-EXTENDED,
551 ;;; :FILTERED, :NUMERIC, and :FINAL. Each rendering depends on the preceding
552 ;;; one, so asking for :FINAL will implicitly compute all renderings.
553 (defun gen-arg-forms (arg rendering funstate
)
554 (let* ((arg-cell (assq arg funstate
))
555 (rendering-temps (cdr (assq rendering
(cdr arg-cell
))))
556 (vars (car rendering-temps
))
557 (forms (cdr rendering-temps
)))
559 (multiple-value-bind (new-forms single-value-p
)
560 (%gen-arg-forms arg rendering funstate
)
561 (setq forms new-forms
562 vars
(cond ((or single-value-p
(atom forms
))
563 (if (symbolp forms
) vars
(sb!xc
:gensym
"_")))
564 ((every #'symbolp forms
)
565 ;; just use the same as the forms
568 (make-gensym-list (length forms
) "_"))))
569 (push (list* rendering vars forms
) (cdr arg-cell
))))
572 (defun maybe-listify (forms)
575 ((/= (length forms
) 1)
580 ;;; DEFINE-ARG-TYPE Name {Key Value}*
582 ;;; Define a disassembler argument type NAME (which can then be referenced in
583 ;;; another argument definition using the :TYPE argument). &KEY args are:
585 ;;; :SIGN-EXTEND boolean
586 ;;; If non-NIL, the raw value of this argument is sign-extended.
588 ;;; :TYPE arg-type-name
589 ;;; Inherit any properties of given arg-type.
591 ;;; :PREFILTER function
592 ;;; A function which is called (along with all other prefilters,
593 ;;; in the order that their arguments appear in the instruction-
594 ;;; format) before any printing is done, to filter the raw value.
595 ;;; Any uses of READ-SUFFIX must be done inside a prefilter.
597 ;;; :PRINTER function-string-or-vector
598 ;;; A function, string, or vector which is used to print an argument of
602 ;;; If non-NIL, the value of an argument of this type is used as
603 ;;; an address, and if that address occurs inside the disassembled
604 ;;; code, it is replaced by a label. If this is a function, it is
605 ;;; called to filter the value.
606 (defmacro define-arg-type
(name &rest args
607 &key
((:type inherit
))
608 sign-extend prefilter printer use-label
)
609 (declare (ignore sign-extend prefilter printer use-label
))
610 ;; FIXME: this should be an *unevaluated* macro arg (named :INHERIT)
611 (aver (typep inherit
'(or null
(cons (eql quote
) (cons symbol null
)))))
612 (let ((pair (cons name
(loop for
(ind val
) on args by
#'cddr
613 unless
(eq ind
:type
)
614 nconc
(list ind val
)))))
616 (eval-when (:compile-toplevel
)
617 (%def-arg-type
',name
,inherit
,@(massage-arg pair
:compile
)))
618 #-sb-xc-host
; Host doesn't need the real definition.
619 (%def-arg-type
',name
,inherit
,@(massage-arg pair
:eval
)))))
621 (defun %def-arg-type
(name inherit
&rest properties
)
622 (setf (get name
'arg-type
)
623 (apply 'modify-arg
(%make-arg name
) nil
624 (nconc (when inherit
(list :type inherit
)) properties
))))
626 (defun %gen-arg-forms
(arg rendering funstate
)
627 (declare (type arg arg
) (type list funstate
))
629 (:raw
; just extract the bits
630 (mapcar (lambda (bytespec)
631 `(the (unsigned-byte ,(byte-size bytespec
))
632 (local-extract ',bytespec
)))
634 (:sign-extended
; sign-extend, or not
635 (let ((raw-forms (gen-arg-forms arg
:raw funstate
)))
636 (if (and (arg-sign-extend-p arg
) (listp raw-forms
))
637 (mapcar (lambda (form field
)
638 `(the (signed-byte ,(byte-size field
))
639 (sign-extend ,form
,(byte-size field
))))
643 (:filtered
; extract from the prefiltered value vector
644 (let ((pf (arg-prefilter arg
)))
646 (values `(local-filtered-value ,(arg-position arg funstate
)) t
)
647 (gen-arg-forms arg
:sign-extended funstate
))))
648 (:numeric
; pass the filtered value to the label adjuster, or not
649 (let ((filtered-forms (gen-arg-forms arg
:filtered funstate
))
650 (use-label (arg-use-label arg
)))
651 ;; use-label = T means that the prefiltered value is already an address,
652 ;; otherwise non-nil means a function to call, and NIL means not a label.
653 ;; So only the middle case needs to call ADJUST-LABEL.
654 (if (and use-label
(neq use-label t
))
655 `((adjust-label ,(maybe-listify filtered-forms
) ,use-label
))
657 (:final
; if arg is not a label, return numeric value, otherwise a string
658 (let ((numeric-forms (gen-arg-forms arg
:numeric funstate
)))
659 (if (arg-use-label arg
)
660 `((lookup-label ,(maybe-listify numeric-forms
)))
663 (defun find-printer-fun (printer-source args cache
*current-instruction-flavor
*)
664 (let* ((source (preprocess-printer printer-source args
))
665 (funstate (make-funstate args
))
666 (forms (let ((sb!xc
:*gensym-counter
* 0))
667 (compile-printer-list source funstate
)))
668 (bindings (make-arg-temp-bindings funstate
))
669 (guts `(let* ,bindings
,@forms
))
670 (sub-table (assq :printer cache
)))
671 (or (cdr (assoc guts
(cdr sub-table
) :test
#'equal-mod-gensyms
))
673 '(lambda (chunk inst stream dstate
674 &aux
(chunk (truly-the dchunk chunk
))
675 (inst (truly-the instruction inst
))
676 (stream (truly-the stream stream
))
677 (dstate (truly-the disassem-state dstate
)))
678 (macrolet ((local-format-arg (arg fmt
)
679 `(funcall (formatter ,fmt
) stream
,arg
)))
680 (flet ((local-tab-to-arg-column ()
681 (tab (dstate-argument-column dstate
) stream
))
683 (princ (inst-print-name inst
) stream
))
684 (local-write-char (ch)
685 (write-char ch stream
))
687 (princ thing stream
))
688 (local-princ16 (thing)
689 (princ16 thing stream
))
690 (local-call-arg-printer (arg printer
)
691 (funcall printer arg stream dstate
))
692 (local-call-global-printer (fun)
693 (funcall fun chunk inst stream dstate
))
694 (local-filtered-value (offset)
695 (declare (type filtered-value-index offset
))
696 (aref (dstate-filtered-values dstate
) offset
))
697 (local-extract (bytespec)
698 (dchunk-extract chunk bytespec
))
700 (or (gethash lab
(dstate-label-hash dstate
))
702 (adjust-label (val adjust-fun
)
703 (funcall adjust-fun val dstate
)))
704 (declare (ignorable #'local-tab-to-arg-column
706 #'local-princ
#'local-princ16
708 #'local-call-arg-printer
709 #'local-call-global-printer
711 #'local-filtered-value
712 #'lookup-label
#'adjust-label
)
713 (inline local-tab-to-arg-column
714 local-princ local-princ16
715 local-call-arg-printer local-call-global-printer
716 local-filtered-value local-extract
717 lookup-label adjust-label
))
719 (cdar (push (cons guts
(compile nil
(subst guts
:body template
)))
720 (cdr sub-table
)))))))
722 (defun preprocess-test (subj form args
)
723 (multiple-value-bind (subj test
)
724 (if (and (consp form
) (symbolp (car form
)) (not (keywordp (car form
))))
725 (values (car form
) (cdr form
))
727 (let ((key (if (consp test
) (car test
) test
))
728 (body (if (consp test
) (cdr test
) nil
)))
732 ;; If no supplied constant values, just any constant is ok,
733 ;; just see whether there's some constant value in the arg.
737 (or (find subj args
:key
#'arg-name
)
738 (pd-error "unknown argument ~S" subj
)))))
739 ;; Otherwise, defer to run-time.
750 (preprocess-test subj sub-test args
))
754 (defun preprocess-conditionals (printer args
)
759 (preprocess-conditionals
760 `(:cond
((:not
,(nth 1 printer
)) ,@(nthcdr 2 printer
)))
763 (preprocess-conditionals `(:cond
(,(cdr printer
))) args
))
765 (preprocess-conditionals
766 `(:cond
(,(nth 1 printer
) ,(nth 2 printer
))
767 (t ,(nth 3 printer
)))
777 (lambda (sub-printer)
778 (preprocess-conditionals sub-printer args
))
782 (preprocess-test (find-first-field-name filtered-body
)
790 (lambda (sub-printer)
791 (preprocess-conditionals sub-printer args
))
794 ;;; Return a version of the disassembly-template PRINTER with
795 ;;; compile-time tests (e.g. :constant without a value), and any
796 ;;; :CHOOSE operators resolved properly for the args ARGS.
798 ;;; (:CHOOSE Sub*) simply returns the first Sub in which every field
799 ;;; reference refers to a valid arg.
800 (defun preprocess-printer (printer args
)
801 (preprocess-conditionals (preprocess-chooses printer args
) args
))
803 ;;; Return the first non-keyword symbol in a depth-first search of TREE.
804 (defun find-first-field-name (tree)
807 ((and (symbolp tree
) (not (keywordp tree
)))
811 ((eq (car tree
) 'quote
)
814 (or (find-first-field-name (car tree
))
815 (find-first-field-name (cdr tree
))))))
817 (defun preprocess-chooses (printer args
)
818 (cond ((atom printer
)
820 ((eq (car printer
) :choose
)
821 (pick-printer-choice (cdr printer
) args
))
823 (sharing-mapcar (lambda (sub) (preprocess-chooses sub args
))
826 ;;;; some simple functions that help avoid consing when we're just
827 ;;;; recursively filtering things that usually don't change
829 (defun sharing-cons (old-cons car cdr
)
831 "If CAR is eq to the car of OLD-CONS and CDR is eq to the CDR, return
832 OLD-CONS, otherwise return (cons CAR CDR)."
833 (if (and (eq car
(car old-cons
)) (eq cdr
(cdr old-cons
)))
837 (defun sharing-mapcar (fun list
)
838 (declare (type function fun
))
840 "A simple (one list arg) mapcar that avoids consing up a new list
841 as long as the results of calling FUN on the elements of LIST are
845 (funcall fun
(car list
))
846 (sharing-mapcar fun
(cdr list
)))))
848 (defun all-arg-refs-relevant-p (printer args
)
849 (cond ((or (null printer
) (keywordp printer
) (eq printer t
))
852 (find printer args
:key
#'arg-name
))
854 (every (lambda (x) (all-arg-refs-relevant-p x args
))
858 (defun pick-printer-choice (choices args
)
859 (dolist (choice choices
860 (pd-error "no suitable choice found in ~S" choices
))
861 (when (all-arg-refs-relevant-p choice args
)
864 (defun compile-printer-list (sources funstate
)
865 (unless (null sources
)
866 ;; Coalesce adjacent symbols/strings, and convert to strings if possible,
867 ;; since they require less consing to write.
868 (do ((el (car sources
) (car sources
))
869 (names nil
(cons (strip-quote el
) names
)))
870 ((not (string-or-qsym-p el
))
872 ;; concatenate adjacent strings and symbols
876 (mapcar #'string
(nreverse names
)))))
877 ;; WTF? Everything else using INST-PRINT-NAME writes a string.
878 (push (if (some #'alpha-char-p string
)
879 `',(make-symbol string
) ; Preserve casifying output.
883 (cons (compile-printer-body (car sources
) funstate
)
884 (compile-printer-list (cdr sources
) funstate
))))
886 (defun compile-printer-body (source funstate
)
892 `(local-tab-to-arg-column))
894 (pd-error "unknown printer element: ~S" source
))
896 (compile-print source funstate
))
898 `(local-princ ',source
))
899 ((eq (car source
) :using
)
900 (unless (or (stringp (cadr source
))
901 (and (listp (cadr source
))
902 (eq (caadr source
) 'function
)))
903 (pd-error "The first arg to :USING must be a string or #'function."))
904 ;; For (:using #'F) to be stuffed in properly, the printer as expressed
905 ;; in its DSL would have to compile-time expand into a thing that
906 ;; reconstructs it such that #'F forms don't appear inside quoted list
907 ;; structure. Lacking the ability to do that, we treat #'F as a bit of
908 ;; syntax to be evaluated manually.
909 (compile-print (caddr source
) funstate
910 (let ((f (cadr source
)))
911 (if (typep f
'(cons (eql function
) (cons symbol null
)))
912 (symbol-function (second f
))
914 ((eq (car source
) :plus-integer
)
915 ;; prints the given field proceed with a + or a -
917 (arg-value-form (arg-or-lose (cadr source
) funstate
)
922 (local-write-char #\
+))
923 (local-princ ,form
))))
924 ((eq (car source
) 'quote
)
925 `(local-princ ,source
))
926 ((eq (car source
) 'function
)
927 `(local-call-global-printer ,source
))
928 ((eq (car source
) :cond
)
929 `(cond ,@(mapcar (lambda (clause)
930 `(,(compile-test (find-first-field-name
934 ,@(compile-printer-list (cdr clause
)
937 ;; :IF, :UNLESS, and :WHEN are replaced by :COND during preprocessing
939 `(progn ,@(compile-printer-list source funstate
)))))
941 (defun compile-print (arg-name funstate
&optional printer
)
942 (let* ((arg (arg-or-lose arg-name funstate
))
943 (printer (or printer
(arg-printer arg
))))
946 `(local-format-arg ,(arg-value-form arg funstate
) ,printer
))
948 `(local-princ (aref ,printer
,(arg-value-form arg funstate
:numeric
))))
949 ((or function
(cons (eql function
)))
950 `(local-call-arg-printer ,(arg-value-form arg funstate
) ,printer
))
952 `(,(if (arg-use-label arg
) 'local-princ16
'local-princ
)
953 ,(arg-value-form arg funstate
))))))
955 (defun string-or-qsym-p (thing)
958 (eq (car thing
) 'quote
)
959 (or (stringp (cadr thing
))
960 (symbolp (cadr thing
))))))
962 (defun strip-quote (thing)
963 (if (and (consp thing
) (eq (car thing
) 'quote
))
967 (defun compare-fields-form (val-form-1 val-form-2
)
968 (flet ((listify-fields (fields)
969 (cond ((symbolp fields
) fields
)
970 ((every #'constantp fields
) `',fields
)
971 (t `(list ,@fields
)))))
972 (cond ((or (symbolp val-form-1
) (symbolp val-form-2
))
973 `(equal ,(listify-fields val-form-1
)
974 ,(listify-fields val-form-2
)))
976 `(and ,@(mapcar (lambda (v1 v2
) `(= ,v1
,v2
))
977 val-form-1 val-form-2
))))))
979 (defun compile-test (subj test funstate
)
980 (when (and (consp test
) (symbolp (car test
)) (not (keywordp (car test
))))
981 (setf subj
(car test
)
983 (let ((key (if (consp test
) (car test
) test
))
984 (body (if (consp test
) (cdr test
) nil
)))
990 (let* ((arg (arg-or-lose subj funstate
))
991 (fields (arg-fields arg
))
993 (when (not (= (length fields
) (length consts
)))
994 (pd-error "The number of constants doesn't match number of ~
995 fields in: (~S :constant~{ ~S~})"
997 (compare-fields-form (gen-arg-forms arg
:numeric funstate
)
1000 `(> ,(arg-value-form (arg-or-lose subj funstate
) funstate
:numeric
)
1003 `(< ,(arg-value-form (arg-or-lose subj funstate
) funstate
:numeric
)
1006 (let ((arg1 (arg-or-lose subj funstate
))
1007 (arg2 (arg-or-lose (car body
) funstate
)))
1008 (unless (and (= (length (arg-fields arg1
))
1009 (length (arg-fields arg2
)))
1010 (every (lambda (bs1 bs2
)
1011 (= (byte-size bs1
) (byte-size bs2
)))
1014 (pd-error "can't compare differently sized fields: ~
1015 (~S :same-as ~S)" subj
(car body
)))
1016 (compare-fields-form (gen-arg-forms arg1
:numeric funstate
)
1017 (gen-arg-forms arg2
:numeric funstate
))))
1019 `(or ,@(mapcar (lambda (sub) (compile-test subj sub funstate
))
1022 `(and ,@(mapcar (lambda (sub) (compile-test subj sub funstate
))
1025 `(not ,(compile-test subj
(car body
) funstate
)))
1026 ((and (consp key
) (null body
))
1027 (compile-test subj key funstate
))
1029 (pd-error "bogus test-form: ~S" test
)))))
1031 (defun compute-mask-id (args)
1032 (let ((mask dchunk-zero
)
1034 (dolist (arg args
(values mask id
))
1035 (let ((av (arg-value arg
)))
1037 (do ((fields (arg-fields arg
) (cdr fields
))
1038 (values (if (atom av
) (list av
) av
) (cdr values
)))
1040 (let ((field-mask (dchunk-make-mask (car fields
))))
1041 (when (/= (dchunk-and mask field-mask
) dchunk-zero
)
1042 (pd-error "The field ~S in arg ~S overlaps some other field."
1045 (dchunk-insertf id
(car fields
) (car values
))
1046 (dchunk-orf mask field-mask
))))))))
1048 #!-sb-fluid
(declaim (inline bytes-to-bits
))
1049 (declaim (maybe-inline sign-extend aligned-p align tab tab0
))
1051 (defun bytes-to-bits (bytes)
1052 (declare (type disassem-length bytes
))
1053 (* bytes sb
!vm
:n-byte-bits
))
1055 (defun bits-to-bytes (bits)
1056 (declare (type disassem-length bits
))
1057 (multiple-value-bind (bytes rbits
)
1058 (truncate bits sb
!vm
:n-byte-bits
)
1059 (when (not (zerop rbits
))
1060 (error "~W bits is not a byte-multiple." bits
))
1063 (defun sign-extend (int size
)
1064 (declare (type integer int
)
1065 (type (integer 0 128) size
))
1066 (if (logbitp (1- size
) int
)
1067 (dpb int
(byte size
0) -
1)
1070 ;;; Is ADDRESS aligned on a SIZE byte boundary?
1071 (defun aligned-p (address size
)
1072 (declare (type address address
)
1073 (type alignment size
))
1074 (zerop (logand (1- size
) address
)))
1076 ;;; Return ADDRESS aligned *upward* to a SIZE byte boundary.
1077 (defun align (address size
)
1078 (declare (type address address
)
1079 (type alignment size
))
1080 (logandc1 (1- size
) (+ (1- size
) address
)))
1082 (defun tab (column stream
)
1083 (funcall (formatter "~V,1t") stream column
)
1085 (defun tab0 (column stream
)
1086 (funcall (formatter "~V,0t") stream column
)
1089 (defun princ16 (value stream
)
1090 (write value
:stream stream
:radix t
:base
16 :escape nil
))
1092 (defstruct (storage-info (:copier nil
))
1093 (groups nil
:type list
) ; alist of (name . location-group)
1094 (debug-vars #() :type vector
))
1096 (defstruct (segment (:conc-name seg-
)
1097 (:constructor %make-segment
)
1099 (sap-maker (missing-arg)
1100 :type
(function () sb
!sys
:system-area-pointer
))
1101 ;; Length in bytes of the range of memory covered by this segment.
1102 (length 0 :type disassem-length
)
1103 (virtual-location 0 :type address
)
1104 (storage-info nil
:type
(or null storage-info
))
1105 ;; KLUDGE: CODE-COMPONENT is not a type the host understands
1106 #-sb-xc-host
(code nil
:type
(or null sb
!kernel
:code-component
))
1107 (unboxed-data-range nil
:type
(or null
(cons fixnum fixnum
)))
1108 (hooks nil
:type list
))
1110 ;;; All state during disassembly. We store some seemingly redundant
1111 ;;; information so that we can allow garbage collect during disassembly and
1112 ;;; not get tripped up by a code block being moved...
1113 (defstruct (disassem-state (:conc-name dstate-
)
1114 (:constructor %make-dstate
)
1116 ;; offset of current pos in segment
1117 (cur-offs 0 :type offset
)
1118 ;; offset of next position
1119 (next-offs 0 :type offset
)
1120 ;; a sap pointing to our segment
1121 (segment-sap nil
:type
(or null sb
!sys
:system-area-pointer
))
1122 ;; the current segment
1123 (segment nil
:type
(or null segment
))
1124 ;; what to align to in most cases
1125 (alignment sb
!vm
:n-word-bytes
:type alignment
)
1126 (byte-order :little-endian
1127 :type
(member :big-endian
:little-endian
))
1128 ;; for user code to hang stuff off of
1129 (properties nil
:type list
)
1130 ;; for user code to hang stuff off of, cleared each time after a
1131 ;; non-prefix instruction is processed
1132 (inst-properties nil
:type list
)
1133 (filtered-values (make-array max-filtered-value-index
)
1134 :type filtered-value-vector
)
1135 ;; used for prettifying printing
1136 (addr-print-len nil
:type
(or null
(integer 0 20)))
1137 (argument-column 0 :type column
)
1138 ;; to make output look nicer
1139 (output-state :beginning
1140 :type
(member :beginning
1144 ;; alist of (address . label-number)
1145 (labels nil
:type list
)
1146 ;; same as LABELS slot data, but in a different form
1147 (label-hash (make-hash-table) :type hash-table
)
1149 (fun-hooks nil
:type list
)
1151 ;; alist of (address . label-number), popped as it's used
1152 (cur-labels nil
:type list
)
1153 ;; OFFS-HOOKs, popped as they're used
1154 (cur-offs-hooks nil
:type list
)
1156 ;; for the current location
1157 (notes nil
:type list
)
1159 ;; currently active source variables
1160 (current-valid-locations nil
:type
(or null
(vector bit
))))
1161 (defmethod print-object ((dstate disassem-state
) stream
)
1162 (print-unreadable-object (dstate stream
:type t
)
1165 (dstate-cur-offs dstate
)
1166 (dstate-segment dstate
))))
1168 ;;; Return the absolute address of the current instruction in DSTATE.
1169 (defun dstate-cur-addr (dstate)
1170 (the address
(+ (seg-virtual-location (dstate-segment dstate
))
1171 (dstate-cur-offs dstate
))))
1173 ;;; Return the absolute address of the next instruction in DSTATE.
1174 (defun dstate-next-addr (dstate)
1175 (the address
(+ (seg-virtual-location (dstate-segment dstate
))
1176 (dstate-next-offs dstate
))))
1178 ;;; Get the value of the property called NAME in DSTATE. Also SETF'able.
1180 ;;; KLUDGE: The associated run-time machinery for this is in
1181 ;;; target-disassem.lisp (much later). This is here just to make sure
1182 ;;; it's defined before it's used. -- WHN ca. 19990701
1183 (defmacro dstate-get-prop
(dstate name
)
1184 `(getf (dstate-properties ,dstate
) ,name
))
1186 ;;; Push NAME on the list of instruction properties in DSTATE.
1187 (defun dstate-put-inst-prop (dstate name
)
1188 (push name
(dstate-inst-properties dstate
)))
1190 ;;; Return non-NIL if NAME is on the list of instruction properties in
1192 (defun dstate-get-inst-prop (dstate name
)
1193 (member name
(dstate-inst-properties dstate
) :test
#'eq
))
1195 (declaim (ftype function read-suffix
))
1196 (defun read-signed-suffix (length dstate
)
1197 (declare (type (member 8 16 32 64) length
)
1198 (type disassem-state dstate
)
1199 (optimize (speed 3) (safety 0)))
1200 (sign-extend (read-suffix length dstate
) length
))