Remove all warnings in compilation of 'disassem'
[sbcl.git] / src / compiler / disassem.lisp
blob8306191450fe3127910a0a13f3edb30f98d06b0f
1 ;;;; machine-independent disassembler
3 ;;;; This software is part of the SBCL system. See the README file for
4 ;;;; more information.
5 ;;;;
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 #.sb!vm:n-word-bits))
22 (deftype disassem-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
33 ;;; instructions
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 ;; How many columns of output to allow for the address preceding each line.
44 ;; If NIL, use the minimum possible width for the disassembly range.
45 ;; If 0, do not print addresses.
46 (defvar *disassem-location-column-width* nil)
47 (declaim (type (or null text-width) *disassem-location-column-width*))
49 ;;; the width of the column in which instruction-names are printed. A
50 ;;; value of zero gives the effect of not aligning the arguments at
51 ;;; all.
52 (defvar *disassem-opcode-column-width* 0)
53 (declaim (type text-width *disassem-opcode-column-width*))
55 ;;; the width of the column in which instruction-bytes are printed. A
56 ;;; value of zero disables the printing of instruction bytes.
57 (defvar *disassem-inst-column-width* 16
58 #!+sb-doc
59 "The width of instruction bytes.")
60 (declaim (type text-width *disassem-inst-column-width*))
62 (defvar *disassem-note-column* (+ 45 *disassem-inst-column-width*)
63 #!+sb-doc
64 "The column in which end-of-line comments for notes are started.")
66 ;;;; cached functions
67 ;;;;
68 ;;;; There's no need for 1000 different versions of a function equivalent
69 ;;;; to (PROGN (PRINT ADDR) (PRINT OPCODE) (PRINT ARG)) so we try to
70 ;;;; coalesce sexprs, since there is no such thing as coalescing compiled code.
71 ;;;; This is not really a "cache" as much as hashtable for coalescing.
73 (defstruct (fun-cache (:copier nil)
74 (:print-object (lambda (self stream)
75 (print-unreadable-object
76 (self stream :type t :identity t)))))
77 (serial-number 0 :type fixnum)
78 (printers nil :type list)
79 (labellers nil :type list)
80 (prefilters nil :type list))
82 (defvar *disassem-fun-cache* (make-fun-cache))
83 (declaim (type fun-cache *disassem-fun-cache*))
85 ;;;; A DCHUNK contains the bits we look at to decode an
86 ;;;; instruction.
87 ;;;; I tried to keep this abstract so that if using integers > the machine
88 ;;;; word size conses too much, it can be changed to use bit-vectors or
89 ;;;; something.
90 ;;;;
91 ;;;; KLUDGE: It's not clear that using bit-vectors would be any more efficient.
92 ;;;; Perhaps the abstraction could go away. -- WHN 19991124
94 #!-sb-fluid
95 (declaim (inline dchunk-or dchunk-and dchunk-clear dchunk-not
96 dchunk-make-mask dchunk-make-field
97 sap-ref-dchunk
98 dchunk-extract
99 dchunk=
100 dchunk-count-bits))
102 (def!constant dchunk-bits #.sb!vm:n-word-bits)
104 (deftype dchunk ()
105 `(unsigned-byte ,dchunk-bits))
106 (deftype dchunk-index ()
107 `(integer 0 ,dchunk-bits))
109 (def!constant dchunk-zero 0)
110 (def!constant dchunk-one #.(1- (expt 2 sb!vm:n-word-bits)))
112 (defun dchunk-extract (from pos)
113 (declare (type dchunk from))
114 (the dchunk (ldb pos (the dchunk from))))
116 (defmacro dchunk-copy (x)
117 `(the dchunk ,x))
119 (defun dchunk-or (to from)
120 (declare (type dchunk to from))
121 (the dchunk (logior to from)))
122 (defun dchunk-and (to from)
123 (declare (type dchunk to from))
124 (the dchunk (logand to from)))
125 (defun dchunk-clear (to from)
126 (declare (type dchunk to from))
127 (the dchunk (logandc2 to from)))
128 (defun dchunk-not (from)
129 (declare (type dchunk from))
130 (the dchunk (logand dchunk-one (lognot from))))
132 (defmacro dchunk-andf (to from)
133 `(setf ,to (dchunk-and ,to ,from)))
134 (defmacro dchunk-orf (to from)
135 `(setf ,to (dchunk-or ,to ,from)))
136 (defmacro dchunk-clearf (to from)
137 `(setf ,to (dchunk-clear ,to ,from)))
139 (defun dchunk-make-mask (pos)
140 (the dchunk (mask-field pos -1)))
141 (defun dchunk-make-field (pos value)
142 (the dchunk (dpb value pos 0)))
144 (defmacro make-dchunk (value)
145 `(the dchunk ,value))
147 #-sb-xc-host ;; FIXME: function belongs in 'target-disassem'
148 (defun sap-ref-dchunk (sap byte-offset byte-order)
149 (declare (type sb!sys:system-area-pointer sap)
150 (type offset byte-offset)
151 (muffle-conditions compiler-note) ; returns possible bignum
152 (optimize (speed 3) (safety 0)))
153 (the dchunk
154 (ecase dchunk-bits
155 (32 (if (eq byte-order :big-endian)
156 (+ (ash (sb!sys:sap-ref-8 sap byte-offset) 24)
157 (ash (sb!sys:sap-ref-8 sap (+ 1 byte-offset)) 16)
158 (ash (sb!sys:sap-ref-8 sap (+ 2 byte-offset)) 8)
159 (sb!sys:sap-ref-8 sap (+ 3 byte-offset)))
160 (+ (sb!sys:sap-ref-8 sap byte-offset)
161 (ash (sb!sys:sap-ref-8 sap (+ 1 byte-offset)) 8)
162 (ash (sb!sys:sap-ref-8 sap (+ 2 byte-offset)) 16)
163 (ash (sb!sys:sap-ref-8 sap (+ 3 byte-offset)) 24))))
164 (64 (if (eq byte-order :big-endian)
165 (+ (ash (sb!sys:sap-ref-8 sap byte-offset) 56)
166 (ash (sb!sys:sap-ref-8 sap (+ 1 byte-offset)) 48)
167 (ash (sb!sys:sap-ref-8 sap (+ 2 byte-offset)) 40)
168 (ash (sb!sys:sap-ref-8 sap (+ 3 byte-offset)) 32)
169 (ash (sb!sys:sap-ref-8 sap (+ 4 byte-offset)) 24)
170 (ash (sb!sys:sap-ref-8 sap (+ 5 byte-offset)) 16)
171 (ash (sb!sys:sap-ref-8 sap (+ 6 byte-offset)) 8)
172 (sb!sys:sap-ref-8 sap (+ 7 byte-offset)))
173 (+ (sb!sys:sap-ref-8 sap byte-offset)
174 (ash (sb!sys:sap-ref-8 sap (+ 1 byte-offset)) 8)
175 (ash (sb!sys:sap-ref-8 sap (+ 2 byte-offset)) 16)
176 (ash (sb!sys:sap-ref-8 sap (+ 3 byte-offset)) 24)
177 (ash (sb!sys:sap-ref-8 sap (+ 4 byte-offset)) 32)
178 (ash (sb!sys:sap-ref-8 sap (+ 5 byte-offset)) 40)
179 (ash (sb!sys:sap-ref-8 sap (+ 6 byte-offset)) 48)
180 (ash (sb!sys:sap-ref-8 sap (+ 7 byte-offset)) 56)))))))
182 (defun dchunk-corrected-extract (from pos unit-bits byte-order)
183 (declare (type dchunk from))
184 (if (eq byte-order :big-endian)
185 (ldb (byte (byte-size pos)
186 (+ (byte-position pos) (- dchunk-bits unit-bits)))
187 (the dchunk from))
188 (ldb pos (the dchunk from))))
190 (defmacro dchunk-insertf (place pos value)
191 `(setf ,place (the dchunk (dpb ,value ,pos (the dchunk,place)))))
193 (defun dchunk= (x y)
194 (declare (type dchunk x y))
195 (= x y))
196 (defmacro dchunk-zerop (x)
197 `(dchunk= ,x dchunk-zero))
199 (defun dchunk-strict-superset-p (sup sub)
200 (and (zerop (logandc2 sub sup))
201 (not (zerop (logandc2 sup sub)))))
203 (defun dchunk-count-bits (x)
204 (declare (type dchunk x))
205 (logcount x))
207 (defstruct (instruction (:conc-name inst-)
208 (:constructor
209 make-instruction (name
210 format-name
211 print-name
212 length
213 mask id
214 printer
215 labeller prefilter control))
216 (:copier nil))
217 (name nil :type (or symbol string))
218 (format-name nil :type (or symbol string))
220 (mask dchunk-zero :type dchunk) ; bits in the inst that are constant
221 (id dchunk-zero :type dchunk) ; value of those constant bits
223 (length 0 :type disassem-length) ; in bytes
225 (print-name nil :type symbol)
227 ;; disassembly functions
228 (prefilter nil :type (or null function))
229 (labeller nil :type (or null function))
230 (printer (missing-arg) :type (or null function))
231 (control nil :type (or null function))
233 ;; instructions that are the same as this instruction but with more
234 ;; constraints
235 (specializers nil :type list))
236 (def!method print-object ((inst instruction) stream)
237 (print-unreadable-object (inst stream :type t :identity t)
238 (format stream "~A(~A)" (inst-name inst) (inst-format-name inst))))
240 ;;;; an instruction space holds all known machine instructions in a
241 ;;;; form that can be easily searched
243 (defstruct (inst-space (:conc-name ispace-)
244 (:copier nil))
245 (valid-mask dchunk-zero :type dchunk) ; applies to *children*
246 (choices nil :type list))
247 (def!method print-object ((ispace inst-space) stream)
248 (print-unreadable-object (ispace stream :type t :identity t)))
250 ;;; now that we've defined the structure, we can declaim the type of
251 ;;; the variable:
252 (declaim (type (or null inst-space) *disassem-inst-space*))
254 (defstruct (inst-space-choice (:conc-name ischoice-)
255 (:copier nil))
256 (common-id dchunk-zero :type dchunk) ; applies to *parent's* mask
257 (subspace (missing-arg) :type (or inst-space instruction)))
259 ;;;; These are the kind of values we can compute for an argument, and
260 ;;;; how to compute them. The :CHECKER functions make sure that a given
261 ;;;; argument is compatible with another argument for a given use.
263 (defvar *arg-form-kinds* nil)
265 (defstruct (arg-form-kind (:copier nil))
266 (names nil :type list)
267 (producer (missing-arg) :type function)
268 (checker (missing-arg) :type function))
270 (defun arg-form-kind-or-lose (kind)
271 (or (getf *arg-form-kinds* kind)
272 (pd-error "unknown arg-form kind ~S" kind)))
274 (defun find-arg-form-producer (kind)
275 (arg-form-kind-producer (arg-form-kind-or-lose kind)))
276 (defun find-arg-form-checker (kind)
277 (arg-form-kind-checker (arg-form-kind-or-lose kind)))
279 (defun canonicalize-arg-form-kind (kind)
280 (car (arg-form-kind-names (arg-form-kind-or-lose kind))))
282 ;;;; only used during compilation of the instructions for a backend
283 ;;;;
284 ;;;; FIXME: If only used then, isn't there some way we could do
285 ;;;; EVAL-WHEN tricks to keep this stuff from appearing in the target
286 ;;;; system?
288 (defvar *disassem-inst-formats* (make-hash-table))
289 (defvar *disassem-arg-types* nil)
290 (defvar *disassem-fun-cache* (make-fun-cache))
292 (defstruct (arg (:copier nil)
293 (:predicate nil)
294 (:constructor %make-arg (name &optional position))
295 (:constructor standard-make-arg) ; only so #S readmacro works
296 (:print-object
297 (lambda (self stream)
298 (if *print-readably*
299 (call-next-method)
300 (print-unreadable-object (self stream :type t)
301 (format stream
302 "~D:~A ~:[~;+~]~:S~@[=~S~]~@[ filt=~S~]~
303 ~@[ lbl=~S~]~@[ prt=~S~]"
304 (arg-position self)
305 (arg-name self)
306 (arg-sign-extend-p self)
307 (arg-fields self)
308 (arg-value self)
309 (arg-prefilter self)
310 (arg-use-label self)
311 (arg-printer self)))))))
312 (name nil :type symbol)
313 (fields nil :type list)
315 (value nil :type (or list integer))
316 (sign-extend-p nil :type (member t nil))
318 ;; position in a vector of prefiltered values
319 (position 0 :type fixnum)
321 ;; functions to use
322 (printer nil)
323 (prefilter nil)
324 (use-label nil))
326 (defstruct (instruction-format (:conc-name format-)
327 (:constructor make-inst-format
328 (name length default-printer args))
329 (:copier nil))
330 (name nil)
331 (args nil :type list)
333 (length 0 :type disassem-length) ; in bytes
335 (default-printer nil :type list))
337 ;;; A FUNSTATE holds the state of any arguments used in a disassembly
338 ;;; function.
339 (defstruct (funstate (:conc-name funstate-)
340 (:constructor %make-funstate)
341 (:copier nil))
342 (args nil :type list)
343 (arg-temps nil :type list)) ; See below.
345 (defun make-funstate (args)
346 ;; give the args a position
347 (let ((i 0))
348 (dolist (arg args)
349 (setf (arg-position arg) i)
350 (incf i)))
351 (%make-funstate :args args))
353 (defun funstate-compatible-p (funstate args)
354 (every (lambda (this-arg-temps)
355 (let* ((old-arg (car this-arg-temps))
356 (new-arg (find (arg-name old-arg) args :key #'arg-name)))
357 (and new-arg
358 (= (arg-position old-arg) (arg-position new-arg))
359 (every (lambda (this-kind-temps)
360 (funcall (find-arg-form-checker
361 (car this-kind-temps))
362 new-arg
363 old-arg))
364 (cdr this-arg-temps)))))
365 (funstate-arg-temps funstate)))
367 (defun arg-or-lose (name funstate)
368 (let ((arg (find name (funstate-args funstate) :key #'arg-name)))
369 (when (null arg)
370 (pd-error "unknown argument ~S" name))
371 arg))
373 ;;;; Since we can't include some values in compiled output as they are
374 ;;;; (notably functions), we sometimes use a VALSRC structure to keep
375 ;;;; track of the source from which they were derived.
377 (defstruct (valsrc (:constructor %make-valsrc)
378 (:copier nil))
379 (value nil)
380 (source nil))
382 (defun make-valsrc (value source)
383 (cond ((equal value source)
384 source)
385 ((and (listp value) (eq (car value) 'function))
386 value)
388 (%make-valsrc :value value :source source))))
390 ;;; machinery to provide more meaningful error messages during compilation
391 (defvar *current-instruction-flavor* nil)
392 (defun pd-error (fmt &rest args)
393 (if *current-instruction-flavor*
394 (error "~@<in printer-definition for ~S(~S): ~3I~:_~?~:>"
395 (car *current-instruction-flavor*)
396 (cdr *current-instruction-flavor*)
397 fmt args)
398 (apply #'error fmt args)))
400 ;;; FIXME:
401 ;;; 1. This should become a utility in SB!INT.
402 ;;; 2. Arrays and structures and maybe other things are
403 ;;; self-evaluating too.
404 (defun self-evaluating-p (x)
405 (typecase x
406 (null t)
407 (keyword t)
408 (symbol (eq x t))
409 (cons nil)
410 (t t)))
412 (defun maybe-quote (evalp form)
413 (if (or evalp (self-evaluating-p form)) form `',form))
415 ;;; Detect things that obviously don't need wrapping, like
416 ;;; variable-refs and #'function.
417 (defun doesnt-need-wrapping-p (form)
418 (or (symbolp form)
419 (and (listp form)
420 (eq (car form) 'function)
421 (symbolp (cadr form)))))
423 (defun make-wrapper (form arg-name funargs prefix)
424 (if (and (listp form)
425 (eq (car form) 'function))
426 ;; a function def
427 (let ((wrapper-name (symbolicate prefix "-" arg-name "-WRAPPER"))
428 (wrapper-args (make-gensym-list (length funargs))))
429 (values `#',wrapper-name
430 `(defun ,wrapper-name ,wrapper-args
431 (funcall ,form ,@wrapper-args))))
432 ;; something else
433 (let ((wrapper-name (symbolicate "*" prefix "-" arg-name "-WRAPPER*")))
434 (values wrapper-name `(defparameter ,wrapper-name ,form)))))
436 (defun filter-overrides (overrides evalp)
437 (mapcar (lambda (override)
438 (list* (car override) (cadr override)
439 (munge-fun-refs (cddr override) evalp)))
440 overrides))
442 (defparameter *arg-fun-params*
443 '((:printer . (value stream dstate))
444 (:use-label . (value dstate))
445 (:prefilter . (value dstate))))
447 (defun munge-fun-refs (params evalp &optional wrap-defs-p (prefix ""))
448 (let ((params (copy-list params)))
449 (do ((tail params (cdr tail))
450 (wrapper-defs nil))
451 ((null tail)
452 (values params (nreverse wrapper-defs)))
453 (let ((fun-arg (assoc (car tail) *arg-fun-params*)))
454 (when fun-arg
455 (let* ((fun-form (cadr tail))
456 (quoted-fun-form `',fun-form))
457 (when (and wrap-defs-p (not (doesnt-need-wrapping-p fun-form)))
458 (multiple-value-bind (access-form wrapper-def-form)
459 (make-wrapper fun-form (car fun-arg) (cdr fun-arg) prefix)
460 (setf quoted-fun-form `',access-form)
461 (push wrapper-def-form wrapper-defs)))
462 (if evalp
463 (setf (cadr tail)
464 `(make-valsrc ,fun-form ,quoted-fun-form))
465 (setf (cadr tail)
466 fun-form))))))))
468 (defun gen-args-def-form (overrides format-form &optional (evalp t))
469 (let ((args-var (gensym)))
470 `(let ((,args-var (copy-list (format-args ,format-form))))
471 ,@(mapcar (lambda (override)
472 (update-args-form args-var
473 `',(car override)
474 (and (cdr override)
475 (cons :value (cdr override)))
476 evalp))
477 overrides)
478 ,args-var)))
480 (defun gen-printer-def-forms-def-form (base-name
482 &optional
483 (evalp t))
484 (declare (type symbol base-name))
485 (destructuring-bind
486 (format-name
487 (&rest field-defs)
488 &optional (printer-form :default)
489 &key ((:print-name print-name-form) `',base-name) control)
491 (let ((format-var (gensym))
492 (field-defs (filter-overrides field-defs evalp)))
493 `(let* ((*current-instruction-flavor* ',(cons base-name format-name))
494 (,format-var (format-or-lose ',format-name))
495 (args ,(gen-args-def-form field-defs format-var evalp))
496 (funcache *disassem-fun-cache*))
497 (multiple-value-bind (printer-fun printer-defun)
498 (find-printer-fun ,(if (eq printer-form :default)
499 `(format-default-printer ,format-var)
500 (maybe-quote evalp printer-form))
501 args funcache)
502 (multiple-value-bind (labeller-fun labeller-defun)
503 (find-labeller-fun args funcache)
504 (multiple-value-bind (prefilter-fun prefilter-defun)
505 (find-prefilter-fun args funcache)
506 (multiple-value-bind (mask id)
507 (compute-mask-id args)
508 (values
509 `(make-instruction ',',base-name
510 ',',format-name
511 ,',print-name-form
512 ,(format-length ,format-var)
513 ,mask
515 ,(and printer-fun `#',printer-fun)
516 ,(and labeller-fun `#',labeller-fun)
517 ,(and prefilter-fun `#',prefilter-fun)
518 ,',control)
519 `(progn
520 ,@(and printer-defun (list printer-defun))
521 ,@(and labeller-defun (list labeller-defun))
522 ,@(and prefilter-defun (list prefilter-defun))))
523 ))))))))
525 (defun update-args-form (var name-form descrip-forms evalp)
526 `(setf ,var
527 ,(if evalp
528 `(modify-or-add-arg ,name-form ,var ,@descrip-forms)
529 `(apply #'modify-or-add-arg ,name-form ,var ',descrip-forms))))
531 (defun format-or-lose (name)
532 (or (gethash name *disassem-inst-formats*)
533 (pd-error "unknown instruction format ~S" name)))
535 ;;; FIXME: needed only at build-the-system time, not in running system
536 ;;; and FIXME: better syntax would allow inheriting the length to avoid
537 ;;; re-stating it needlessly in some derived formats. Perhaps:
538 ;;; (DEFINE-INSTRUCTION-FORMAT NAME (:bits N [more-format-keys]*) &rest fields)
540 (defmacro define-instruction-format ((format-name length-in-bits
541 &key default-printer include)
542 &rest arg-specs)
543 #!+sb-doc
544 "DEFINE-INSTRUCTION-FORMAT (Name Length {Format-Key Value}*) Arg-Def*
545 Define an instruction format NAME for the disassembler's use. LENGTH is
546 the length of the format in bits.
547 Possible FORMAT-KEYs:
549 :INCLUDE other-format-name
550 Inherit all arguments and properties of the given format. Any
551 arguments defined in the current format definition will either modify
552 the copy of an existing argument (keeping in the same order with
553 respect to when prefilters are called), if it has the same name as
554 one, or be added to the end.
555 :DEFAULT-PRINTER printer-list
556 Use the given PRINTER-LIST as a format to print any instructions of
557 this format when they don't specify something else.
559 Each ARG-DEF defines one argument in the format, and is of the form
560 (Arg-Name {Arg-Key Value}*)
562 Possible ARG-KEYs (the values are evaluated unless otherwise specified):
564 :FIELDS byte-spec-list
565 The argument takes values from these fields in the instruction. If
566 the list is of length one, then the corresponding value is supplied by
567 itself; otherwise it is a list of the values. The list may be NIL.
568 :FIELD byte-spec
569 The same as :FIELDS (list byte-spec).
571 :VALUE value
572 If the argument only has one field, this is the value it should have,
573 otherwise it's a list of the values of the individual fields. This can
574 be overridden in an instruction-definition or a format definition
575 including this one by specifying another, or NIL to indicate that it's
576 variable.
578 :SIGN-EXTEND boolean
579 If non-NIL, the raw value of this argument is sign-extended,
580 immediately after being extracted from the instruction (before any
581 prefilters are run, for instance). If the argument has multiple
582 fields, they are all sign-extended.
584 :TYPE arg-type-name
585 Inherit any properties of the given argument type.
587 :PREFILTER function
588 A function which is called (along with all other prefilters, in the
589 order that their arguments appear in the instruction-format) before
590 any printing is done, to filter the raw value. Any uses of READ-SUFFIX
591 must be done inside a prefilter.
593 :PRINTER function-string-or-vector
594 A function, string, or vector which is used to print this argument.
596 :USE-LABEL
597 If non-NIL, the value of this argument is used as an address, and if
598 that address occurs inside the disassembled code, it is replaced by a
599 label. If this is a function, it is called to filter the value."
600 (let ((length-var (gensym)) ; are lengths ever non-constant? probably not.
601 (inherited-args
602 (if include
603 (copy-list (format-args (format-or-lose include)))))
604 added-args readers all-wrapper-defs)
605 (dolist (arg-spec arg-specs)
606 (let ((arg-name (car arg-spec)))
607 (multiple-value-bind (props wrapper-defs)
608 (munge-fun-refs (cdr arg-spec) t t
609 (symbolicate format-name '- arg-name))
610 (setf all-wrapper-defs (nconc wrapper-defs all-wrapper-defs))
611 (let ((reader (getf props :reader)))
612 (when reader
613 (setq readers (list* #!-sb-fluid `(declaim (inline ,reader))
614 `(defun ,reader (dchunk dstate)
615 (declare (ignorable dchunk dstate))
616 (arg-access-macro ,arg-name ,format-name
617 dchunk dstate))
618 readers))
619 (remf props :reader))) ; ok because MUNGEing copied the plist
620 (let ((cell (member arg-name inherited-args
621 :key (lambda (x)
622 (arg-name (if (listp x) (second x) x))))))
623 (cond ((not cell)
624 (push `(make-arg
625 ,(+ (length inherited-args) (length added-args))
626 ,length-var ',arg-name ,@props)
627 added-args))
628 (props ; do nothing if no alterations
629 (rplaca cell
630 `(copy-arg ,(car cell) ,length-var ,@props))))))))
631 `(progn
632 ,@all-wrapper-defs
633 (eval-when (:compile-toplevel :execute)
634 (let ((,length-var ,length-in-bits))
635 (setf (gethash ',format-name *disassem-inst-formats*)
636 (make-inst-format ',format-name (bits-to-bytes ,length-var)
637 ,(maybe-quote t default-printer)
638 (list ,@inherited-args
639 ,@(nreverse added-args))))))
640 ,@readers)))
642 (defun make-arg (number format-length-bits name &rest properties)
643 (apply #'modify-arg (%make-arg name number) format-length-bits properties))
645 (defun copy-arg (arg format-length-bits &rest properties)
646 (apply #'modify-arg (copy-structure arg) format-length-bits properties))
648 ;;; FIXME: probably needed only at build-the-system time, not in
649 ;;; final target system
650 (defun modify-or-add-arg (arg-name args &rest properties)
651 (declare (dynamic-extent properties))
652 (when (get-properties properties '(:field :fields))
653 (error "~@<in arg ~S: ~3I~:_~
654 can't specify fields except using DEFINE-INSTRUCTION-FORMAT~:>"
655 arg-name))
656 (let* ((cell (member arg-name args :key #'arg-name))
657 (arg (if cell
658 (setf (car cell) (copy-structure (car cell)))
659 (let ((arg (%make-arg arg-name)))
660 (setf args (nconc args (list arg)))
661 arg))))
662 (apply #'modify-arg arg nil properties)
663 args))
665 (defun modify-arg (arg format-length
666 &key (value nil value-p)
667 (type nil type-p)
668 (prefilter nil prefilter-p)
669 (printer nil printer-p)
670 (sign-extend nil sign-extend-p)
671 (use-label nil use-label-p)
672 (field nil field-p)
673 (fields nil fields-p))
674 (when field-p
675 (if fields-p
676 (error ":FIELD and :FIELDS are mutually exclusive")
677 (setf fields (list field) fields-p t)))
678 (when type-p
679 (set-arg-from-type arg type *disassem-arg-types*))
680 (when value-p
681 (setf (arg-value arg) value))
682 (when prefilter-p
683 (setf (arg-prefilter arg) prefilter))
684 (when sign-extend-p
685 (setf (arg-sign-extend-p arg) sign-extend))
686 (when printer-p
687 (setf (arg-printer arg) printer))
688 (when use-label-p
689 (setf (arg-use-label arg) use-label))
690 (when fields-p
691 (setf (arg-fields arg)
692 (mapcar (lambda (bytespec)
693 (when (> (+ (byte-position bytespec) (byte-size bytespec))
694 format-length)
695 (error "~@<in arg ~S: ~3I~:_~
696 The field ~S doesn't fit in an ~
697 instruction-format ~W bits wide.~:>"
698 (arg-name arg) bytespec format-length))
699 (correct-dchunk-bytespec-for-endianness
700 bytespec format-length sb!c:*backend-byte-order*))
701 fields)))
702 arg)
704 ;; Generate a sexpr to extract ARG-NAME of FORMAT-NAME using CHUNK and DSTATE.
705 ;; The first two arguments to this macro are not runtime-evaluated.
706 (defmacro arg-access-macro (arg-name format-name chunk dstate)
707 (let* ((funstate (make-funstate (format-args (format-or-lose format-name))))
708 (arg (arg-or-lose arg-name funstate))
709 (arg-val-form (arg-value-form arg funstate :adjusted)))
710 `(flet ((local-filtered-value (offset)
711 (declare (type filtered-value-index offset))
712 (aref (dstate-filtered-values ,dstate) offset))
713 (local-extract (bytespec)
714 (dchunk-extract ,chunk bytespec)))
715 (declare (ignorable #'local-filtered-value #'local-extract)
716 (inline local-filtered-value local-extract))
717 (let* ,(make-arg-temp-bindings funstate) ,arg-val-form))))
719 (defun arg-value-form (arg funstate
720 &optional
721 (kind :final)
722 (allow-multiple-p (not (eq kind :numeric))))
723 (let ((forms (gen-arg-forms arg kind funstate)))
724 (when (and (not allow-multiple-p)
725 (listp forms)
726 (/= (length forms) 1))
727 (pd-error "~S must not have multiple values." arg))
728 (maybe-listify forms)))
730 (defun correct-dchunk-bytespec-for-endianness (bs unit-bits byte-order)
731 (if (eq byte-order :big-endian)
732 (byte (byte-size bs) (+ (byte-position bs) (- dchunk-bits unit-bits)))
733 bs))
735 (defun make-arg-temp-bindings (funstate)
736 ;; (Everything is in reverse order, so we just use PUSH, which
737 ;; results in everything being in the right order at the end.)
738 (let ((bindings nil))
739 (dolist (ats (funstate-arg-temps funstate))
740 (dolist (atk (cdr ats))
741 (cond ((null (cadr atk)))
742 ((atom (cadr atk))
743 (push `(,(cadr atk) ,(cddr atk)) bindings))
745 (mapc (lambda (var form)
746 (push `(,var ,form) bindings))
747 (cadr atk)
748 (cddr atk))))))
749 bindings))
751 (defun gen-arg-forms (arg kind funstate)
752 (multiple-value-bind (vars forms)
753 (get-arg-temp arg kind funstate)
754 (when (null forms)
755 (multiple-value-bind (new-forms single-value-p)
756 (funcall (find-arg-form-producer kind) arg funstate)
757 (setq forms new-forms)
758 (cond ((or single-value-p (atom forms))
759 (unless (symbolp forms)
760 (setq vars (gensym))))
761 ((every #'symbolp forms)
762 ;; just use the same as the forms
763 (setq vars nil))
765 (setq vars (make-gensym-list (length forms)))))
766 (set-arg-temps vars forms arg kind funstate)))
767 (or vars forms)))
769 (defun maybe-listify (forms)
770 (cond ((atom forms)
771 forms)
772 ((/= (length forms) 1)
773 `(list ,@forms))
775 (car forms))))
777 (defun set-arg-from-type (arg type-name table)
778 (let ((type-arg (find type-name table :key #'arg-name)))
779 (when (null type-arg)
780 (pd-error "unknown argument type: ~S" type-name))
781 (setf (arg-printer arg) (arg-printer type-arg))
782 (setf (arg-prefilter arg) (arg-prefilter type-arg))
783 (setf (arg-sign-extend-p arg) (arg-sign-extend-p type-arg))
784 (setf (arg-use-label arg) (arg-use-label type-arg))))
786 (defun get-arg-temp (arg kind funstate)
787 (let ((this-arg-temps (assoc arg (funstate-arg-temps funstate))))
788 (if this-arg-temps
789 (let ((this-kind-temps
790 (assoc (canonicalize-arg-form-kind kind)
791 (cdr this-arg-temps))))
792 (values (cadr this-kind-temps) (cddr this-kind-temps)))
793 (values nil nil))))
795 (defun set-arg-temps (vars forms arg kind funstate)
796 (let ((this-arg-temps
797 (or (assoc arg (funstate-arg-temps funstate))
798 (car (push (cons arg nil) (funstate-arg-temps funstate)))))
799 (kind (canonicalize-arg-form-kind kind)))
800 (let ((this-kind-temps
801 (or (assoc kind (cdr this-arg-temps))
802 (car (push (cons kind nil) (cdr this-arg-temps))))))
803 (setf (cdr this-kind-temps) (cons vars forms)))))
805 ;;; DEFINE-ARG-TYPE Name {Key Value}*
807 ;;; Define a disassembler argument type NAME (which can then be referenced in
808 ;;; another argument definition using the :TYPE argument). &KEY args are:
810 ;;; :SIGN-EXTEND boolean
811 ;;; If non-NIL, the raw value of this argument is sign-extended.
813 ;;; :TYPE arg-type-name
814 ;;; Inherit any properties of given arg-type.
816 ;;; :PREFILTER function
817 ;;; A function which is called (along with all other prefilters,
818 ;;; in the order that their arguments appear in the instruction-
819 ;;; format) before any printing is done, to filter the raw value.
820 ;;; Any uses of READ-SUFFIX must be done inside a prefilter.
822 ;;; :PRINTER function-string-or-vector
823 ;;; A function, string, or vector which is used to print an argument of
824 ;;; this type.
826 ;;; :USE-LABEL
827 ;;; If non-NIL, the value of an argument of this type is used as
828 ;;; an address, and if that address occurs inside the disassembled
829 ;;; code, it is replaced by a label. If this is a function, it is
830 ;;; called to filter the value.
831 (defmacro define-arg-type (name &rest args
832 &key sign-extend type prefilter printer use-label)
833 (declare (ignore sign-extend type prefilter printer use-label))
834 (multiple-value-bind (args wrapper-defs)
835 (munge-fun-refs args t t name)
836 `(progn
837 ,@wrapper-defs
838 (eval-when (:compile-toplevel :execute)
839 (setq *disassem-arg-types*
840 (delete ',name *disassem-arg-types* :key #'arg-name))
841 (push (modify-arg (%make-arg ',name) nil ,@args) *disassem-arg-types*))
842 ',name)))
844 (defmacro def-arg-form-kind ((&rest names) &rest inits)
845 `(let ((kind (make-arg-form-kind :names ',names ,@inits)))
846 ,@(mapcar (lambda (name)
847 `(setf (getf *arg-form-kinds* ',name) kind))
848 names)))
850 (def-arg-form-kind (:raw)
851 :producer (lambda (arg funstate)
852 (declare (ignore funstate))
853 (mapcar (lambda (bytespec)
854 `(the (unsigned-byte ,(byte-size bytespec))
855 (local-extract ',bytespec)))
856 (arg-fields arg)))
857 :checker (lambda (new-arg old-arg)
858 (equal (arg-fields new-arg)
859 (arg-fields old-arg))))
861 (def-arg-form-kind (:sign-extended :unfiltered)
862 :producer (lambda (arg funstate)
863 (let ((raw-forms (gen-arg-forms arg :raw funstate)))
864 (if (and (arg-sign-extend-p arg) (listp raw-forms))
865 (mapcar (lambda (form field)
866 `(the (signed-byte ,(byte-size field))
867 (sign-extend ,form
868 ,(byte-size field))))
869 raw-forms
870 (arg-fields arg))
871 raw-forms)))
872 :checker (lambda (new-arg old-arg)
873 (equal (arg-sign-extend-p new-arg)
874 (arg-sign-extend-p old-arg))))
876 (defun valsrc-equal (f1 f2)
877 (if (null f1)
878 (null f2)
879 (equal (value-or-source f1)
880 (value-or-source f2))))
882 (def-arg-form-kind (:filtering)
883 :producer (lambda (arg funstate)
884 (let ((sign-extended-forms
885 (gen-arg-forms arg :sign-extended funstate))
886 (pf (arg-prefilter arg)))
887 (if pf
888 (values
889 `(local-filter ,(maybe-listify sign-extended-forms)
890 ,(source-form pf))
892 (values sign-extended-forms nil))))
893 :checker (lambda (new-arg old-arg)
894 (valsrc-equal (arg-prefilter new-arg) (arg-prefilter old-arg))))
896 (def-arg-form-kind (:filtered :unadjusted)
897 :producer (lambda (arg funstate)
898 (let ((pf (arg-prefilter arg)))
899 (if pf
900 (values `(local-filtered-value ,(arg-position arg)) t)
901 (gen-arg-forms arg :sign-extended funstate))))
902 :checker (lambda (new-arg old-arg)
903 (let ((pf1 (arg-prefilter new-arg))
904 (pf2 (arg-prefilter old-arg)))
905 (if (null pf1)
906 (null pf2)
907 (= (arg-position new-arg)
908 (arg-position old-arg))))))
910 (def-arg-form-kind (:adjusted :numeric :unlabelled)
911 :producer (lambda (arg funstate)
912 (let ((filtered-forms (gen-arg-forms arg :filtered funstate))
913 (use-label (arg-use-label arg)))
914 (if (and use-label (not (eq use-label t)))
915 (list
916 `(adjust-label ,(maybe-listify filtered-forms)
917 ,(source-form use-label)))
918 filtered-forms)))
919 :checker (lambda (new-arg old-arg)
920 (valsrc-equal (arg-use-label new-arg) (arg-use-label old-arg))))
922 (def-arg-form-kind (:labelled :final)
923 :producer (lambda (arg funstate)
924 (let ((adjusted-forms
925 (gen-arg-forms arg :adjusted funstate))
926 (use-label (arg-use-label arg)))
927 (if use-label
928 (let ((form (maybe-listify adjusted-forms)))
929 (if (and (not (eq use-label t))
930 (not (atom adjusted-forms))
931 (/= (length adjusted-forms) 1))
932 (pd-error
933 "cannot label a multiple-field argument ~
934 unless using a function: ~S" arg)
935 `((lookup-label ,form))))
936 adjusted-forms)))
937 :checker (lambda (new-arg old-arg)
938 (let ((lf1 (arg-use-label new-arg))
939 (lf2 (arg-use-label old-arg)))
940 (if (null lf1) (null lf2) t))))
942 ;;; This is a bogus kind that's just used to ensure that printers are
943 ;;; compatible...
944 (def-arg-form-kind (:printed)
945 :producer (lambda (&rest noise)
946 (declare (ignore noise))
947 (pd-error "bogus! can't use the :printed value of an arg!"))
948 :checker (lambda (new-arg old-arg)
949 (valsrc-equal (arg-printer new-arg) (arg-printer old-arg))))
951 (defun remember-printer-use (arg funstate)
952 (set-arg-temps nil nil arg :printed funstate))
954 ;;; Returns a version of THING suitable for including in an evaluable
955 ;;; position in some form.
956 (defun source-form (thing)
957 (cond ((valsrc-p thing)
958 (valsrc-source thing))
959 ((functionp thing)
960 (pd-error
961 "can't dump functions, so function ref form must be quoted: ~S"
962 thing))
963 ((self-evaluating-p thing)
964 thing)
965 ((eq (car thing) 'function)
966 thing)
968 `',thing)))
970 ;;; Return anything but a VALSRC structure.
971 (defun value-or-source (thing)
972 (if (valsrc-p thing)
973 (valsrc-value thing)
974 thing))
976 (defstruct (cached-fun (:conc-name cached-fun-)
977 (:copier nil))
978 (funstate nil :type (or null funstate))
979 (constraint nil :type list)
980 (name nil :type (or null symbol)))
982 (defun find-cached-fun (cached-funs args constraint)
983 (dolist (cached-fun cached-funs nil)
984 (let ((funstate (cached-fun-funstate cached-fun)))
985 (when (and (equal constraint (cached-fun-constraint cached-fun))
986 (or (null funstate)
987 (funstate-compatible-p funstate args)))
988 (return cached-fun)))))
990 (defmacro !with-cached-fun ((name-var
991 funstate-var
992 cache
993 cache-slot
994 args
995 &key
996 constraint
997 (stem (missing-arg)))
998 &body defun-maker-forms)
999 (let ((cache-var (gensym))
1000 (constraint-var (gensym)))
1001 `(let* ((,constraint-var ,constraint)
1002 (,cache-var (find-cached-fun (,cache-slot ,cache)
1003 ,args ,constraint-var)))
1004 (cond (,cache-var
1005 (values (cached-fun-name ,cache-var) nil))
1007 (let* ((,name-var
1008 (symbolicate
1009 ,stem
1010 (write-to-string (incf (fun-cache-serial-number cache)))))
1011 (,funstate-var (make-funstate ,args))
1012 (,cache-var
1013 (make-cached-fun :name ,name-var
1014 :funstate ,funstate-var
1015 :constraint ,constraint-var)))
1016 (values ,name-var
1017 `(progn
1018 ,(progn ,@defun-maker-forms)
1019 (eval-when (:compile-toplevel :execute)
1020 (push ,,cache-var
1021 (,',cache-slot ',,cache)))))))))))
1023 (defun find-printer-fun (printer-source args cache)
1024 (if (null printer-source)
1025 (values nil nil)
1026 (let ((printer-source (preprocess-printer printer-source args)))
1027 (!with-cached-fun
1028 (name funstate cache fun-cache-printers args
1029 :constraint printer-source
1030 :stem "INST-PRINTER-")
1031 (make-printer-defun printer-source funstate name)))))
1033 (defun make-printer-defun (source funstate fun-name)
1034 (let ((printer-form (compile-printer-list source funstate))
1035 (bindings (make-arg-temp-bindings funstate)))
1036 `(defun ,fun-name (chunk inst stream dstate)
1037 (declare (type dchunk chunk)
1038 (type instruction inst)
1039 (type stream stream)
1040 (type disassem-state dstate))
1041 (macrolet ((local-format-arg (arg fmt)
1042 `(funcall (formatter ,fmt) stream ,arg)))
1043 (flet ((local-tab-to-arg-column ()
1044 (tab (dstate-argument-column dstate) stream))
1045 (local-print-name ()
1046 (princ (inst-print-name inst) stream))
1047 (local-write-char (ch)
1048 (write-char ch stream))
1049 (local-princ (thing)
1050 (princ thing stream))
1051 (local-princ16 (thing)
1052 (princ16 thing stream))
1053 (local-call-arg-printer (arg printer)
1054 (funcall printer arg stream dstate))
1055 (local-call-global-printer (fun)
1056 (funcall fun chunk inst stream dstate))
1057 (local-filtered-value (offset)
1058 (declare (type filtered-value-index offset))
1059 (aref (dstate-filtered-values dstate) offset))
1060 (local-extract (bytespec)
1061 (dchunk-extract chunk bytespec))
1062 (lookup-label (lab)
1063 (or (gethash lab (dstate-label-hash dstate))
1064 lab))
1065 (adjust-label (val adjust-fun)
1066 (funcall adjust-fun val dstate)))
1067 (declare (ignorable #'local-tab-to-arg-column
1068 #'local-print-name
1069 #'local-princ #'local-princ16
1070 #'local-write-char
1071 #'local-call-arg-printer
1072 #'local-call-global-printer
1073 #'local-extract
1074 #'local-filtered-value
1075 #'lookup-label #'adjust-label)
1076 (inline local-tab-to-arg-column
1077 local-princ local-princ16
1078 local-call-arg-printer local-call-global-printer
1079 local-filtered-value local-extract
1080 lookup-label adjust-label))
1081 (let* ,bindings
1082 ,@printer-form))))))
1084 (defun preprocess-test (subj form args)
1085 (multiple-value-bind (subj test)
1086 (if (and (consp form) (symbolp (car form)) (not (keywordp (car form))))
1087 (values (car form) (cdr form))
1088 (values subj form))
1089 (let ((key (if (consp test) (car test) test))
1090 (body (if (consp test) (cdr test) nil)))
1091 (case key
1092 (:constant
1093 (if (null body)
1094 ;; If no supplied constant values, just any constant is ok,
1095 ;; just see whether there's some constant value in the arg.
1096 (not
1097 (null
1098 (arg-value
1099 (or (find subj args :key #'arg-name)
1100 (pd-error "unknown argument ~S" subj)))))
1101 ;; Otherwise, defer to run-time.
1102 form))
1103 ((:or :and :not)
1104 (sharing-cons
1105 form
1106 subj
1107 (sharing-cons
1108 test
1110 (sharing-mapcar
1111 (lambda (sub-test)
1112 (preprocess-test subj sub-test args))
1113 body))))
1114 (t form)))))
1116 (defun preprocess-conditionals (printer args)
1117 (if (atom printer)
1118 printer
1119 (case (car printer)
1120 (:unless
1121 (preprocess-conditionals
1122 `(:cond ((:not ,(nth 1 printer)) ,@(nthcdr 2 printer)))
1123 args))
1124 (:when
1125 (preprocess-conditionals `(:cond (,(cdr printer))) args))
1126 (:if
1127 (preprocess-conditionals
1128 `(:cond (,(nth 1 printer) ,(nth 2 printer))
1129 (t ,(nth 3 printer)))
1130 args))
1131 (:cond
1132 (sharing-cons
1133 printer
1134 :cond
1135 (sharing-mapcar
1136 (lambda (clause)
1137 (let ((filtered-body
1138 (sharing-mapcar
1139 (lambda (sub-printer)
1140 (preprocess-conditionals sub-printer args))
1141 (cdr clause))))
1142 (sharing-cons
1143 clause
1144 (preprocess-test (find-first-field-name filtered-body)
1145 (car clause)
1146 args)
1147 filtered-body)))
1148 (cdr printer))))
1149 (quote printer)
1151 (sharing-mapcar
1152 (lambda (sub-printer)
1153 (preprocess-conditionals sub-printer args))
1154 printer)))))
1156 ;;; Return a version of the disassembly-template PRINTER with
1157 ;;; compile-time tests (e.g. :constant without a value), and any
1158 ;;; :CHOOSE operators resolved properly for the args ARGS.
1160 ;;; (:CHOOSE Sub*) simply returns the first Sub in which every field
1161 ;;; reference refers to a valid arg.
1162 (defun preprocess-printer (printer args)
1163 (preprocess-conditionals (preprocess-chooses printer args) args))
1165 ;;; Return the first non-keyword symbol in a depth-first search of TREE.
1166 (defun find-first-field-name (tree)
1167 (cond ((null tree)
1168 nil)
1169 ((and (symbolp tree) (not (keywordp tree)))
1170 tree)
1171 ((atom tree)
1172 nil)
1173 ((eq (car tree) 'quote)
1174 nil)
1176 (or (find-first-field-name (car tree))
1177 (find-first-field-name (cdr tree))))))
1179 (defun preprocess-chooses (printer args)
1180 (cond ((atom printer)
1181 printer)
1182 ((eq (car printer) :choose)
1183 (pick-printer-choice (cdr printer) args))
1185 (sharing-mapcar (lambda (sub) (preprocess-chooses sub args))
1186 printer))))
1188 ;;;; some simple functions that help avoid consing when we're just
1189 ;;;; recursively filtering things that usually don't change
1191 (defun sharing-cons (old-cons car cdr)
1192 #!+sb-doc
1193 "If CAR is eq to the car of OLD-CONS and CDR is eq to the CDR, return
1194 OLD-CONS, otherwise return (cons CAR CDR)."
1195 (if (and (eq car (car old-cons)) (eq cdr (cdr old-cons)))
1196 old-cons
1197 (cons car cdr)))
1199 (defun sharing-mapcar (fun list)
1200 (declare (type function fun))
1201 #!+sb-doc
1202 "A simple (one list arg) mapcar that avoids consing up a new list
1203 as long as the results of calling FUN on the elements of LIST are
1204 eq to the original."
1205 (and list
1206 (sharing-cons list
1207 (funcall fun (car list))
1208 (sharing-mapcar fun (cdr list)))))
1210 (defun all-arg-refs-relevant-p (printer args)
1211 (cond ((or (null printer) (keywordp printer) (eq printer t))
1213 ((symbolp printer)
1214 (find printer args :key #'arg-name))
1215 ((listp printer)
1216 (every (lambda (x) (all-arg-refs-relevant-p x args))
1217 printer))
1218 (t t)))
1220 (defun pick-printer-choice (choices args)
1221 (dolist (choice choices
1222 (pd-error "no suitable choice found in ~S" choices))
1223 (when (all-arg-refs-relevant-p choice args)
1224 (return choice))))
1226 (defun compile-printer-list (sources funstate)
1227 (unless (null sources)
1228 ;; Coalesce adjacent symbols/strings, and convert to strings if possible,
1229 ;; since they require less consing to write.
1230 (do ((el (car sources) (car sources))
1231 (names nil (cons (strip-quote el) names)))
1232 ((not (string-or-qsym-p el))
1233 (when names
1234 ;; concatenate adjacent strings and symbols
1235 (let ((string
1236 (apply #'concatenate
1237 'string
1238 (mapcar #'string (nreverse names)))))
1239 (push (if (some #'alpha-char-p string)
1240 `',(make-symbol string) ; Preserve casifying output.
1241 string)
1242 sources))))
1243 (pop sources))
1244 (cons (compile-printer-body (car sources) funstate)
1245 (compile-printer-list (cdr sources) funstate))))
1247 (defun compile-printer-body (source funstate)
1248 (cond ((null source)
1249 nil)
1250 ((eq source :name)
1251 `(local-print-name))
1252 ((eq source :tab)
1253 `(local-tab-to-arg-column))
1254 ((keywordp source)
1255 (pd-error "unknown printer element: ~S" source))
1256 ((symbolp source)
1257 (compile-print source funstate))
1258 ((atom source)
1259 `(local-princ ',source))
1260 ((eq (car source) :using)
1261 (unless (or (stringp (cadr source))
1262 (and (listp (cadr source))
1263 (eq (caadr source) 'function)))
1264 (pd-error "The first arg to :USING must be a string or #'function."))
1265 (compile-print (caddr source) funstate
1266 (make-valsrc (eval (cadr source)) (cadr source))))
1267 ((eq (car source) :plus-integer)
1268 ;; prints the given field proceed with a + or a -
1269 (let ((form
1270 (arg-value-form (arg-or-lose (cadr source) funstate)
1271 funstate
1272 :numeric)))
1273 `(progn
1274 (when (>= ,form 0)
1275 (local-write-char #\+))
1276 (local-princ ,form))))
1277 ((eq (car source) 'quote)
1278 `(local-princ ,source))
1279 ((eq (car source) 'function)
1280 `(local-call-global-printer ,source))
1281 ((eq (car source) :cond)
1282 `(cond ,@(mapcar (lambda (clause)
1283 `(,(compile-test (find-first-field-name
1284 (cdr clause))
1285 (car clause)
1286 funstate)
1287 ,@(compile-printer-list (cdr clause)
1288 funstate)))
1289 (cdr source))))
1290 ;; :IF, :UNLESS, and :WHEN are replaced by :COND during preprocessing
1292 `(progn ,@(compile-printer-list source funstate)))))
1294 (defun compile-print (arg-name funstate &optional printer)
1295 (let* ((arg (arg-or-lose arg-name funstate))
1296 (printer (or printer (arg-printer arg)))
1297 (printer-val (value-or-source printer))
1298 (printer-src (source-form printer)))
1299 (remember-printer-use arg funstate)
1300 (cond ((stringp printer-val)
1301 `(local-format-arg ,(arg-value-form arg funstate) ,printer-val))
1302 ((vectorp printer-val)
1303 `(local-princ
1304 (aref ,printer-src
1305 ,(arg-value-form arg funstate :numeric))))
1306 ((or (functionp printer-val)
1307 (and (consp printer-val) (eq (car printer-val) 'function)))
1308 `(local-call-arg-printer ,(arg-value-form arg funstate)
1309 ,printer-src))
1310 ((or (null printer-val) (eq printer-val t))
1311 `(,(if (arg-use-label arg) 'local-princ16 'local-princ)
1312 ,(arg-value-form arg funstate)))
1314 (pd-error "illegal printer: ~S" printer-src)))))
1316 (defun string-or-qsym-p (thing)
1317 (or (stringp thing)
1318 (and (consp thing)
1319 (eq (car thing) 'quote)
1320 (or (stringp (cadr thing))
1321 (symbolp (cadr thing))))))
1323 (defun strip-quote (thing)
1324 (if (and (consp thing) (eq (car thing) 'quote))
1325 (cadr thing)
1326 thing))
1328 (defun compare-fields-form (val-form-1 val-form-2)
1329 (flet ((listify-fields (fields)
1330 (cond ((symbolp fields) fields)
1331 ((every #'constantp fields) `',fields)
1332 (t `(list ,@fields)))))
1333 (cond ((or (symbolp val-form-1) (symbolp val-form-2))
1334 `(equal ,(listify-fields val-form-1)
1335 ,(listify-fields val-form-2)))
1337 `(and ,@(mapcar (lambda (v1 v2) `(= ,v1 ,v2))
1338 val-form-1 val-form-2))))))
1340 (defun compile-test (subj test funstate)
1341 (when (and (consp test) (symbolp (car test)) (not (keywordp (car test))))
1342 (setf subj (car test)
1343 test (cdr test)))
1344 (let ((key (if (consp test) (car test) test))
1345 (body (if (consp test) (cdr test) nil)))
1346 (cond ((null key)
1347 nil)
1348 ((eq key t)
1350 ((eq key :constant)
1351 (let* ((arg (arg-or-lose subj funstate))
1352 (fields (arg-fields arg))
1353 (consts body))
1354 (when (not (= (length fields) (length consts)))
1355 (pd-error "The number of constants doesn't match number of ~
1356 fields in: (~S :constant~{ ~S~})"
1357 subj body))
1358 (compare-fields-form (gen-arg-forms arg :numeric funstate)
1359 consts)))
1360 ((eq key :positive)
1361 `(> ,(arg-value-form (arg-or-lose subj funstate) funstate :numeric)
1363 ((eq key :negative)
1364 `(< ,(arg-value-form (arg-or-lose subj funstate) funstate :numeric)
1366 ((eq key :same-as)
1367 (let ((arg1 (arg-or-lose subj funstate))
1368 (arg2 (arg-or-lose (car body) funstate)))
1369 (unless (and (= (length (arg-fields arg1))
1370 (length (arg-fields arg2)))
1371 (every (lambda (bs1 bs2)
1372 (= (byte-size bs1) (byte-size bs2)))
1373 (arg-fields arg1)
1374 (arg-fields arg2)))
1375 (pd-error "can't compare differently sized fields: ~
1376 (~S :same-as ~S)" subj (car body)))
1377 (compare-fields-form (gen-arg-forms arg1 :numeric funstate)
1378 (gen-arg-forms arg2 :numeric funstate))))
1379 ((eq key :or)
1380 `(or ,@(mapcar (lambda (sub) (compile-test subj sub funstate))
1381 body)))
1382 ((eq key :and)
1383 `(and ,@(mapcar (lambda (sub) (compile-test subj sub funstate))
1384 body)))
1385 ((eq key :not)
1386 `(not ,(compile-test subj (car body) funstate)))
1387 ((and (consp key) (null body))
1388 (compile-test subj key funstate))
1390 (pd-error "bogus test-form: ~S" test)))))
1392 (defun find-labeller-fun (args cache)
1393 (let ((labelled-fields
1394 (mapcar #'arg-name (remove-if-not #'arg-use-label args))))
1395 (if (null labelled-fields)
1396 (values nil nil)
1397 (!with-cached-fun
1398 (name funstate cache fun-cache-labellers args
1399 :stem "INST-LABELLER-"
1400 :constraint labelled-fields)
1401 (let ((labels-form 'labels))
1402 (dolist (arg args)
1403 (when (arg-use-label arg)
1404 (setf labels-form
1405 `(let ((labels ,labels-form)
1406 (addr
1407 ,(arg-value-form arg funstate :adjusted nil)))
1408 ;; if labeler didn't return an integer, it isn't a label
1409 (if (or (not (integerp addr)) (assoc addr labels))
1410 labels
1411 (cons (cons addr nil) labels))))))
1412 `(defun ,name (chunk labels dstate)
1413 (declare (type list labels)
1414 (type dchunk chunk)
1415 (type disassem-state dstate))
1416 (flet ((local-filtered-value (offset)
1417 (declare (type filtered-value-index offset))
1418 (aref (dstate-filtered-values dstate) offset))
1419 (local-extract (bytespec)
1420 (dchunk-extract chunk bytespec))
1421 (adjust-label (val adjust-fun)
1422 (funcall adjust-fun val dstate)))
1423 (declare (ignorable #'local-filtered-value #'local-extract
1424 #'adjust-label)
1425 (inline local-filtered-value local-extract
1426 adjust-label))
1427 (let* ,(make-arg-temp-bindings funstate)
1428 ,labels-form))))))))
1430 (defun find-prefilter-fun (args cache)
1431 (let ((filtered-args (mapcar #'arg-name
1432 (remove-if-not #'arg-prefilter args))))
1433 (if (null filtered-args)
1434 (values nil nil)
1435 (!with-cached-fun
1436 (name funstate cache fun-cache-prefilters args
1437 :stem "INST-PREFILTER-"
1438 :constraint filtered-args)
1439 (collect ((forms))
1440 (dolist (arg args)
1441 (let ((pf (arg-prefilter arg)))
1442 (when pf
1443 (forms
1444 `(setf (local-filtered-value ,(arg-position arg))
1445 ,(maybe-listify
1446 (gen-arg-forms arg :filtering funstate)))))
1448 `(defun ,name (chunk dstate)
1449 (declare (type dchunk chunk)
1450 (type disassem-state dstate))
1451 (flet (((setf local-filtered-value) (value offset)
1452 (declare (type filtered-value-index offset))
1453 (setf (aref (dstate-filtered-values dstate) offset)
1454 value))
1455 (local-filter (value filter)
1456 (funcall filter value dstate))
1457 (local-extract (bytespec)
1458 (dchunk-extract chunk bytespec)))
1459 (declare (ignorable #'local-filter #'local-extract)
1460 (inline (setf local-filtered-value)
1461 local-filter local-extract))
1462 ;; Use them for side effects only.
1463 (let* ,(make-arg-temp-bindings funstate)
1464 ,@(forms)))))))))
1466 (defun compute-mask-id (args)
1467 (let ((mask dchunk-zero)
1468 (id dchunk-zero))
1469 (dolist (arg args (values mask id))
1470 (let ((av (arg-value arg)))
1471 (when av
1472 (do ((fields (arg-fields arg) (cdr fields))
1473 (values (if (atom av) (list av) av) (cdr values)))
1474 ((null fields))
1475 (let ((field-mask (dchunk-make-mask (car fields))))
1476 (when (/= (dchunk-and mask field-mask) dchunk-zero)
1477 (pd-error "The field ~S in arg ~S overlaps some other field."
1478 (car fields)
1479 (arg-name arg)))
1480 (dchunk-insertf id (car fields) (car values))
1481 (dchunk-orf mask field-mask))))))))
1483 (defun install-inst-flavors (name flavors)
1484 (setf (gethash name *disassem-insts*)
1485 flavors))
1487 #!-sb-fluid (declaim (inline bytes-to-bits))
1488 (declaim (maybe-inline sign-extend aligned-p align tab tab0))
1490 (defun bytes-to-bits (bytes)
1491 (declare (type disassem-length bytes))
1492 (* bytes sb!vm:n-byte-bits))
1494 (defun bits-to-bytes (bits)
1495 (declare (type disassem-length bits))
1496 (multiple-value-bind (bytes rbits)
1497 (truncate bits sb!vm:n-byte-bits)
1498 (when (not (zerop rbits))
1499 (error "~W bits is not a byte-multiple." bits))
1500 bytes))
1502 (defun sign-extend (int size)
1503 (declare (type integer int)
1504 (type (integer 0 128) size))
1505 (if (logbitp (1- size) int)
1506 (dpb int (byte size 0) -1)
1507 int))
1509 ;;; Is ADDRESS aligned on a SIZE byte boundary?
1510 (defun aligned-p (address size)
1511 (declare (type address address)
1512 (type alignment size))
1513 (zerop (logand (1- size) address)))
1515 ;;; Return ADDRESS aligned *upward* to a SIZE byte boundary.
1516 (defun align (address size)
1517 (declare (type address address)
1518 (type alignment size))
1519 (logandc1 (1- size) (+ (1- size) address)))
1521 (defun tab (column stream)
1522 (funcall (formatter "~V,1t") stream column)
1523 nil)
1524 (defun tab0 (column stream)
1525 (funcall (formatter "~V,0t") stream column)
1526 nil)
1528 (defun princ16 (value stream)
1529 (write value :stream stream :radix t :base 16 :escape nil))
1531 (defun read-signed-suffix (length dstate)
1532 (declare (type (member 8 16 32 64) length)
1533 (type disassem-state dstate)
1534 (optimize (speed 3) (safety 0)))
1535 (sign-extend (read-suffix length dstate) length))
1537 (defstruct (storage-info (:copier nil))
1538 (groups nil :type list) ; alist of (name . location-group)
1539 (debug-vars #() :type vector))
1541 (defstruct (segment (:conc-name seg-)
1542 (:constructor %make-segment)
1543 (:copier nil))
1544 (sap-maker (missing-arg)
1545 :type (function () sb!sys:system-area-pointer))
1546 ;; Length in bytes of the range of memory covered by this segment.
1547 (length 0 :type disassem-length)
1548 ;; Length of the memory range excluding any trailing untagged data.
1549 ;; Defaults to 'length' but could be shorter.
1550 ;; FIXME: can opcodes-length really be shorter? Nothing ever alters it.
1551 (opcodes-length 0 :type disassem-length)
1552 (virtual-location 0 :type address)
1553 (storage-info nil :type (or null storage-info))
1554 ;; KLUDGE: CODE-COMPONENT is not a type the host understands
1555 #-sb-xc-host (code nil :type (or null sb!kernel:code-component))
1556 (unboxed-data-range nil :type (or null (cons fixnum fixnum)))
1557 (hooks nil :type list))
1559 ;;; All state during disassembly. We store some seemingly redundant
1560 ;;; information so that we can allow garbage collect during disassembly and
1561 ;;; not get tripped up by a code block being moved...
1562 (defstruct (disassem-state (:conc-name dstate-)
1563 (:constructor %make-dstate)
1564 (:copier nil))
1565 ;; offset of current pos in segment
1566 (cur-offs 0 :type offset)
1567 ;; offset of next position
1568 (next-offs 0 :type offset)
1569 ;; a sap pointing to our segment
1570 (segment-sap nil :type (or null sb!sys:system-area-pointer))
1571 ;; the current segment
1572 (segment nil :type (or null segment))
1573 ;; what to align to in most cases
1574 (alignment sb!vm:n-word-bytes :type alignment)
1575 (byte-order :little-endian
1576 :type (member :big-endian :little-endian))
1577 ;; for user code to hang stuff off of
1578 (properties nil :type list)
1579 ;; for user code to hang stuff off of, cleared each time after a
1580 ;; non-prefix instruction is processed
1581 (inst-properties nil :type list)
1582 (filtered-values (make-array max-filtered-value-index)
1583 :type filtered-value-vector)
1584 ;; used for prettifying printing
1585 (addr-print-len nil :type (or null (integer 0 20)))
1586 (argument-column 0 :type column)
1587 ;; to make output look nicer
1588 (output-state :beginning
1589 :type (member :beginning
1590 :block-boundary
1591 nil))
1593 ;; alist of (address . label-number)
1594 (labels nil :type list)
1595 ;; same as LABELS slot data, but in a different form
1596 (label-hash (make-hash-table) :type hash-table)
1597 ;; list of function
1598 (fun-hooks nil :type list)
1600 ;; alist of (address . label-number), popped as it's used
1601 (cur-labels nil :type list)
1602 ;; OFFS-HOOKs, popped as they're used
1603 (cur-offs-hooks nil :type list)
1605 ;; for the current location
1606 (notes nil :type list)
1608 ;; currently active source variables
1609 (current-valid-locations nil :type (or null (vector bit))))
1610 (def!method print-object ((dstate disassem-state) stream)
1611 (print-unreadable-object (dstate stream :type t)
1612 (format stream
1613 "+~W~@[ in ~S~]"
1614 (dstate-cur-offs dstate)
1615 (dstate-segment dstate))))
1617 ;;; Return the absolute address of the current instruction in DSTATE.
1618 (defun dstate-cur-addr (dstate)
1619 (the address (+ (seg-virtual-location (dstate-segment dstate))
1620 (dstate-cur-offs dstate))))
1622 ;;; Return the absolute address of the next instruction in DSTATE.
1623 (defun dstate-next-addr (dstate)
1624 (the address (+ (seg-virtual-location (dstate-segment dstate))
1625 (dstate-next-offs dstate))))
1627 ;;; Get the value of the property called NAME in DSTATE. Also SETF'able.
1629 ;;; KLUDGE: The associated run-time machinery for this is in
1630 ;;; target-disassem.lisp (much later). This is here just to make sure
1631 ;;; it's defined before it's used. -- WHN ca. 19990701
1632 (defmacro dstate-get-prop (dstate name)
1633 `(getf (dstate-properties ,dstate) ,name))
1635 ;;; Push NAME on the list of instruction properties in DSTATE.
1636 (defun dstate-put-inst-prop (dstate name)
1637 (push name (dstate-inst-properties dstate)))
1639 ;;; Return non-NIL if NAME is on the list of instruction properties in
1640 ;;; DSTATE.
1641 (defun dstate-get-inst-prop (dstate name)
1642 (member name (dstate-inst-properties dstate) :test #'eq))