Initial revision
[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 (file-comment
17   "$Header$")
18
19 ;;; Generate trace-file output for the byte compiler back-end.
20 ;;;
21 ;;; (Note: As of sbcl-0.6.7, this is target-only code not because it's
22 ;;; logically target-only, but just because it's still implemented in
23 ;;; terms of SAPs.)
24 #!+sb-show
25 (defun describe-byte-component (component xeps segment *standard-output*)
26   (format t "~|~%;;;; byte component ~S~2%" (component-name component))
27   (format t ";;; functions:~%")
28   (dolist (fun (component-lambdas component))
29     (when (leaf-name fun)
30       (let ((info (leaf-info fun)))
31         (when info
32           (format t "~6D: ~S~%"
33                   (sb!assem:label-position (byte-lambda-info-label info))
34                   (leaf-name fun))))))
35
36   (format t "~%;;;disassembly:~2%")
37   (collect ((eps)
38             (chunks))
39     (dolist (x xeps)
40       (let ((xep (cdr x)))
41         (etypecase xep
42           (simple-byte-function
43            (eps (simple-byte-function-entry-point xep)))
44           (hairy-byte-function
45            (dolist (ep (hairy-byte-function-entry-points xep))
46              (eps ep))
47                (when (hairy-byte-function-more-args-entry-point xep)
48                  (eps (hairy-byte-function-more-args-entry-point xep)))))))
49     ;; In CMU CL, this was
50     ;;   (SB!ASSEM:SEGMENT-MAP-OUTPUT
51     ;;      SEGMENT
52     ;;      #'(LAMBDA (SAP BYTES) (CHUNKS (CONS SAP BYTES))))
53     ;; -- WHN 19990811
54     (sb!assem:on-segment-contents-vectorly segment
55                                            (lambda (chunk) (chunks chunk)))
56     (let* ((total-bytes (reduce #'+ (mapcar #'cdr (chunks))))
57            ;; KLUDGE: It's not clear that BUF has to be a SAP instead
58            ;; of a nice high-level, safe, friendly vector. Perhaps
59            ;; this code could be rewritten to use ordinary indices and
60            ;; vectors instead of SAP references to chunks of raw
61            ;; system memory? -- WHN 19990811
62            (buf (allocate-system-memory total-bytes)))
63       (let ((offset 0))
64         (dolist (chunk (chunks))
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
69       (disassem-byte-sap buf
70                          total-bytes
71                          (map 'vector
72                               #'(lambda (x)
73                                   (if (constant-p x)
74                                       (constant-value x)
75                                       x))
76                               (byte-component-info-constants
77                                (component-info component)))
78                          (sort (eps) #'<))
79       (terpri)
80       (deallocate-system-memory buf total-bytes)
81       (values))))
82
83 ;;; Given a byte-compiled function, disassemble it to standard output.
84 (defun disassem-byte-fun (xep)
85   (declare (optimize (inhibit-warnings 3)))
86   (disassem-byte-component
87    (byte-function-component xep)
88    (etypecase xep
89      (simple-byte-function
90       (list (simple-byte-function-entry-point xep)))
91      (hairy-byte-function
92       (sort (copy-list
93              (if (hairy-byte-function-more-args-entry-point xep)
94                  (cons (hairy-byte-function-more-args-entry-point xep)
95                        (hairy-byte-function-entry-points xep))
96                  (hairy-byte-function-entry-points xep)))
97             #'<)))))
98
99 ;;; Given a byte-compiled component, disassemble it to standard output.
100 ;;; EPS is a list of the entry points.
101 (defun disassem-byte-component (component &optional (eps '(0)))
102   (let* ((bytes (* (code-header-ref component sb!vm:code-code-size-slot)
103                    sb!vm:word-bytes))
104          (num-consts (- (get-header-data component)
105                         sb!vm:code-constants-offset))
106          (consts (make-array num-consts)))
107     (dotimes (i num-consts)
108       (setf (aref consts i)
109             (code-header-ref component (+ i sb!vm:code-constants-offset))))
110     (without-gcing
111       (disassem-byte-sap (code-instructions component) bytes
112                          consts eps))
113     (values)))
114
115 ;;; Disassemble byte code from a SAP and constants vector.
116 (defun disassem-byte-sap (sap bytes constants eps)
117   (declare (optimize (inhibit-warnings 3)))
118   (let ((index 0))
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 "~12T~?" 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                                             `((= (logand byte ,(caar clause))
179                                                  ,(cadar clause))
180                                               ,@(cdr clause)))
181                                         clauses))))
182             (dispatch
183              ((#b11110000 #b00000000)
184               (let ((op (extract-4-bit-op byte)))
185                 (note "push-local ~D" op)))
186              ((#b11110000 #b00010000)
187               (let ((op (extract-4-bit-op byte)))
188                 (note "push-arg ~D" op)))
189              ((#b11110000 #b00100000)
190               (let ((*print-level* 3)
191                     (*print-lines* 2))
192                 (note "push-const ~S" (get-constant (extract-4-bit-op byte)))))
193              ((#b11110000 #b00110000)
194               (let ((op (extract-4-bit-op byte))
195                     (*print-level* 3)
196                     (*print-lines* 2))
197                 (note "push-sys-const ~S"
198                       (svref *system-constants* op))))
199              ((#b11110000 #b01000000)
200               (let ((op (extract-4-bit-op byte)))
201                 (note "push-int ~D" op)))
202              ((#b11110000 #b01010000)
203               (let ((op (extract-4-bit-op byte)))
204                 (note "push-neg-int ~D" (- (1+ op)))))
205              ((#b11110000 #b01100000)
206               (let ((op (extract-4-bit-op byte)))
207                 (note "pop-local ~D" op)))
208              ((#b11110000 #b01110000)
209               (let ((op (extract-4-bit-op byte)))
210                 (note "pop-n ~D" op)))
211              ((#b11110000 #b10000000)
212               (let ((op (extract-3-bit-op byte)))
213                 (note "~:[~;named-~]call, ~D args"
214                       (logbitp 3 byte) op)))
215              ((#b11110000 #b10010000)
216               (let ((op (extract-3-bit-op byte)))
217                 (note "~:[~;named-~]tail-call, ~D args"
218                       (logbitp 3 byte) op)))
219              ((#b11110000 #b10100000)
220               (let ((op (extract-3-bit-op byte)))
221                 (note "~:[~;named-~]multiple-call, ~D args"
222                       (logbitp 3 byte) op)))
223              ((#b11111000 #b10110000)
224               ;; local call
225               (let ((op (extract-3-bit-op byte))
226                     (target (extract-24-bits)))
227                 (note "local call ~D, ~D args" target op)))
228              ((#b11111000 #b10111000)
229               ;; local tail-call
230               (let ((op (extract-3-bit-op byte))
231                     (target (extract-24-bits)))
232                 (note "local tail-call ~D, ~D args" target op)))
233              ((#b11111000 #b11000000)
234               ;; local-multiple-call
235               (let ((op (extract-3-bit-op byte))
236                     (target (extract-24-bits)))
237                 (note "local multiple-call ~D, ~D args" target op)))
238              ((#b11111000 #b11001000)
239               ;; return
240               (let ((op (extract-3-bit-op byte)))
241                 (note "return, ~D vals" op)))
242              ((#b11111110 #b11010000)
243               ;; branch
244               (note "branch ~D" (extract-branch-target byte)))
245              ((#b11111110 #b11010010)
246               ;; if-true
247               (note "if-true ~D" (extract-branch-target byte)))
248              ((#b11111110 #b11010100)
249               ;; if-false
250               (note "if-false ~D" (extract-branch-target byte)))
251              ((#b11111110 #b11010110)
252               ;; if-eq
253               (note "if-eq ~D" (extract-branch-target byte)))
254              ((#b11111000 #b11011000)
255               ;; XOP
256               (let* ((low-3-bits (extract-3-bit-op byte))
257                      (xop (nth (if (eq low-3-bits :var) (next-byte) low-3-bits)
258                                *xop-names*)))
259                 (note "xop ~A~@[ ~D~]"
260                       xop
261                       (case xop
262                         ((catch go unwind-protect)
263                          (extract-24-bits))
264                         ((type-check push-n-under)
265                          (get-constant (extract-extended-op)))))))
266
267              ((#b11100000 #b11100000)
268               ;; inline
269               (note "inline ~A"
270                     (inline-function-info-function
271                      (svref *inline-functions* (ldb (byte 5 0) byte))))))))))))