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