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