8b8d9773645da686562fd247705ae44a79a1d73a
[sbcl.git] / src / compiler / target-byte-comp.lisp
1 ;;;; This file contains the noise to byte-compile stuff. It uses the
2 ;;;; same front end as the real compiler, but generates byte code
3 ;;;; instead of native code.
4
5 ;;;; This software is part of the SBCL system. See the README file for
6 ;;;; more information.
7 ;;;;
8 ;;;; This software is derived from the CMU CL system, which was
9 ;;;; written at Carnegie Mellon University and released into the
10 ;;;; public domain. The software is in the public domain and is
11 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
12 ;;;; files for more information.
13
14 (in-package "SB!C")
15
16 ;;; Generate trace-file output for the byte compiler back-end.
17 ;;;
18 ;;; (Note: As of sbcl-0.6.7, this is target-only code not because it's
19 ;;; logically target-only, but just because it's still implemented in
20 ;;; terms of SAPs.)
21 (defun describe-byte-component (component xeps segment *standard-output*)
22   (format t "~|~%;;;; byte component ~S~2%" (component-name component))
23   (format t ";;; functions:~%")
24   (dolist (fun (component-lambdas component))
25     (when (leaf-name fun)
26       (let ((info (leaf-info fun)))
27         (when info
28           (format t "~6D: ~S~%"
29                   (sb!assem:label-position (byte-lambda-info-label info))
30                   (leaf-name fun))))))
31
32   (format t "~%;;;disassembly:~2%")
33   (collect ((eps)
34             (chunks))
35     (dolist (x xeps)
36       (let ((xep (cdr x)))
37         (etypecase xep
38           (simple-byte-function
39            (eps (simple-byte-function-entry-point xep)))
40           (hairy-byte-function
41            (dolist (ep (hairy-byte-function-entry-points xep))
42              (eps ep))
43                (when (hairy-byte-function-more-args-entry-point xep)
44                  (eps (hairy-byte-function-more-args-entry-point xep)))))))
45     ;; In CMU CL, this was
46     ;;   (SB!ASSEM:SEGMENT-MAP-OUTPUT
47     ;;      SEGMENT
48     ;;      #'(LAMBDA (SAP BYTES) (CHUNKS (CONS SAP BYTES))))
49     ;; -- WHN 19990811
50     (sb!assem:on-segment-contents-vectorly segment
51                                            (lambda (chunk) (chunks chunk)))
52     (flet ((chunk-n-bytes (chunk) (length chunk)))
53       (let* ((total-bytes (reduce #'+ (chunks) :key #'chunk-n-bytes))
54              ;; FIXME: It's not clear that BUF has to be a SAP instead
55              ;; of a nice high-level, safe, friendly vector. Perhaps
56              ;; this code could be rewritten to use ordinary indices and
57              ;; vectors instead of SAP references to chunks of raw
58              ;; system memory? Failing that, the DEALLOCATE-SYSTEM-MEMORY
59              ;; operation below should probably be tied to the
60              ;; allocation here with an UNWIND-PROTECT relationship.
61              (buf (allocate-system-memory total-bytes)))
62         (let ((offset 0))
63           (dolist (chunk (chunks))
64             (let ((chunk-n-bits (* (chunk-n-bytes chunk) sb!vm:byte-bits)))
65               (declare (type (simple-array (unsigned-byte 8)) chunk))
66               (copy-byte-vector-to-system-area chunk buf offset)
67               (incf offset chunk-n-bits))))
68         (disassem-byte-sap buf
69                            total-bytes
70                            (map 'vector
71                                 (lambda (x)
72                                   (if (constant-p x)
73                                       (constant-value x)
74                                       x))
75                                 (byte-component-info-constants
76                                  (component-info component)))
77                            (sort (eps) #'<))
78         (terpri)
79         (deallocate-system-memory buf total-bytes)
80         (values)))))
81
82 ;;; Given a byte-compiled function, disassemble it to standard output.
83 (defun disassem-byte-fun (xep)
84   (declare (optimize (inhibit-warnings 3)))
85   (disassem-byte-component
86    (byte-function-component xep)
87    (etypecase xep
88      (simple-byte-function
89       (list (simple-byte-function-entry-point xep)))
90      (hairy-byte-function
91       (sort (copy-list
92              (if (hairy-byte-function-more-args-entry-point xep)
93                  (cons (hairy-byte-function-more-args-entry-point xep)
94                        (hairy-byte-function-entry-points xep))
95                  (hairy-byte-function-entry-points xep)))
96             #'<)))))
97
98 ;;; Given a byte-compiled component, disassemble it to standard
99 ;;; output. EPS is a list of the entry points.
100 (defun disassem-byte-component (component &optional (eps '(0)))
101   (let* ((bytes (* (code-header-ref component sb!vm:code-code-size-slot)
102                    sb!vm:word-bytes))
103          (num-consts (- (get-header-data component)
104                         sb!vm:code-constants-offset))
105          (consts (make-array num-consts)))
106     (dotimes (i num-consts)
107       (setf (aref consts i)
108             (code-header-ref component (+ i sb!vm:code-constants-offset))))
109     (without-gcing
110       (disassem-byte-sap (code-instructions component) bytes
111                          consts eps))
112     (values)))
113
114 ;;; Disassemble byte code from a SAP and constants vector.
115 (defun disassem-byte-sap (sap bytes constants eps)
116   (declare (optimize (inhibit-warnings 3)))
117   (let ((index 0))
118     (declare (type index index))
119     (labels ((newline ()
120                (format t "~&~4D:" index))
121              (next-byte ()
122                (let ((byte (sap-ref-8 sap index)))
123                  (format t " ~2,'0X" byte)
124                  (incf index)
125                  byte))
126              (extract-24-bits ()
127                (logior (ash (next-byte) 16)
128                        (ash (next-byte) 8)
129                        (next-byte)))
130              (extract-extended-op ()
131                (let ((byte (next-byte)))
132                  (if (= byte 255)
133                      (extract-24-bits)
134                      byte)))
135              (extract-4-bit-op (byte)
136                (let ((4-bits (ldb (byte 4 0) byte)))
137                  (if (= 4-bits 15)
138                      (extract-extended-op)
139                      4-bits)))
140              (extract-3-bit-op (byte)
141                (let ((3-bits (ldb (byte 3 0) byte)))
142                  (if (= 3-bits 7)
143                      :var
144                      3-bits)))
145              (extract-branch-target (byte)
146                (if (logbitp 0 byte)
147                    (let ((disp (next-byte)))
148                      (if (logbitp 7 disp)
149                          (+ index disp -256)
150                          (+ index disp)))
151                    (extract-24-bits)))
152              (note (string &rest noise)
153                (format t " ~14T~?" string noise))
154              (get-constant (index)
155                (if (< -1 index (length constants))
156                    (aref constants index)
157                    "<bogus index>")))
158       (loop
159         (unless (< index bytes)
160           (return))
161
162         (when (eql index (first eps))
163           (newline)
164           (pop eps)
165           (let ((frame-size
166                  (let ((byte (next-byte)))
167                    (if (< byte 255)
168                        (* byte 2)
169                        (logior (ash (next-byte) 16)
170                                (ash (next-byte) 8)
171                                (next-byte))))))
172             (note "entry point, frame-size=~D~%" frame-size)))
173
174         (newline)
175         (let ((byte (next-byte)))
176           (macrolet ((dispatch (&rest clauses)
177                        `(cond ,@(mapcar (lambda (clause)
178                                           (destructuring-bind
179                                               ((mask match) &body body)
180                                               clause
181                                             `((= (logand byte ,mask) ,match)
182                                               ,@body)))
183                                         clauses)
184                               (t (error "disassembly failure for bytecode ~X"
185                                         byte)))))
186             (dispatch
187              ((#b11110000 #b00000000)
188               (let ((op (extract-4-bit-op byte)))
189                 (note "push-local ~D" op)))
190              ((#b11110000 #b00010000)
191               (let ((op (extract-4-bit-op byte)))
192                 (note "push-arg ~D" op)))
193              ((#b11110000 #b00100000)
194               ;; FIXME: could use WITH-PRINT-RESTRICTIONS here and in
195               ;; next clause (or just in LABELS NOTE) instead of
196               ;; hand-rolling values in each case here
197               (let ((*print-level* 3)
198                     (*print-lines* 2))
199                 (note "push-const ~S" (get-constant (extract-4-bit-op byte)))))
200              ((#b11110000 #b00110000)
201               (let ((op (extract-4-bit-op byte))
202                     (*print-level* 3)
203                     (*print-lines* 2))
204                 (note "push-sys-const ~S"
205                       (svref *system-constants* op))))
206              ((#b11110000 #b01000000)
207               (let ((op (extract-4-bit-op byte)))
208                 (note "push-int ~D" op)))
209              ((#b11110000 #b01010000)
210               (let ((op (extract-4-bit-op byte)))
211                 (note "push-neg-int ~D" (- (1+ op)))))
212              ((#b11110000 #b01100000)
213               (let ((op (extract-4-bit-op byte)))
214                 (note "pop-local ~D" op)))
215              ((#b11110000 #b01110000)
216               (let ((op (extract-4-bit-op byte)))
217                 (note "pop-n ~D" op)))
218              ((#b11110000 #b10000000)
219               (let ((op (extract-3-bit-op byte)))
220                 (note "~:[~;named-~]call, ~D args"
221                       (logbitp 3 byte) op)))
222              ((#b11110000 #b10010000)
223               (let ((op (extract-3-bit-op byte)))
224                 (note "~:[~;named-~]tail-call, ~D args"
225                       (logbitp 3 byte) op)))
226              ((#b11110000 #b10100000)
227               (let ((op (extract-3-bit-op byte)))
228                 (note "~:[~;named-~]multiple-call, ~D args"
229                       (logbitp 3 byte) op)))
230              ((#b11111000 #b10110000)
231               ;; local call
232               (let ((op (extract-3-bit-op byte))
233                     (target (extract-24-bits)))
234                 (note "local call ~D, ~D args" target op)))
235              ((#b11111000 #b10111000)
236               ;; local tail-call
237               (let ((op (extract-3-bit-op byte))
238                     (target (extract-24-bits)))
239                 (note "local tail-call ~D, ~D args" target op)))
240              ((#b11111000 #b11000000)
241               ;; local-multiple-call
242               (let ((op (extract-3-bit-op byte))
243                     (target (extract-24-bits)))
244                 (note "local multiple-call ~D, ~D args" target op)))
245              ((#b11111000 #b11001000)
246               ;; return
247               (let ((op (extract-3-bit-op byte)))
248                 (note "return, ~D vals" op)))
249              ((#b11111110 #b11010000)
250               ;; branch
251               (note "branch ~D" (extract-branch-target byte)))
252              ((#b11111110 #b11010010)
253               ;; if-true
254               (note "if-true ~D" (extract-branch-target byte)))
255              ((#b11111110 #b11010100)
256               ;; if-false
257               (note "if-false ~D" (extract-branch-target byte)))
258              ((#b11111110 #b11010110)
259               ;; if-eq
260               (note "if-eq ~D" (extract-branch-target byte)))
261              ((#b11111000 #b11011000)
262               ;; XOP
263               (let* ((low-3-bits (extract-3-bit-op byte))
264                      (xop (nth (if (eq low-3-bits :var) (next-byte) low-3-bits)
265                                *xop-names*)))
266                 (note "xop ~A~@[ ~D~]"
267                       xop
268                       (case xop
269                         ((catch go unwind-protect)
270                          (extract-24-bits))
271                         ((type-check push-n-under)
272                          (get-constant (extract-extended-op)))))))
273
274              ((#b11100000 #b11100000)
275               ;; inline
276               (note "inline ~A"
277                     (inline-function-info-function
278                      (svref *inline-functions* (ldb (byte 5 0) byte))))))))))))