196ae9bd2cb3f2468b409f5b40b5bae306d4cceb
[sbcl.git] / src / compiler / byte-comp.lisp
1 ;;;; that part of the byte compiler which exists not only in the
2 ;;;; target Lisp, but also in the cross-compilation host Lisp
3
4 ;;;; This software is part of the SBCL system. See the README file for
5 ;;;; more information.
6 ;;;;
7 ;;;; This software is derived from the CMU CL system, which was
8 ;;;; written at Carnegie Mellon University and released into the
9 ;;;; public domain. The software is in the public domain and is
10 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
11 ;;;; files for more information.
12
13 (in-package "SB!C")
14
15 ;;;; the fasl file format that we use
16 (defconstant byte-fasl-file-version 2)
17 ;;; 1 = before about sbcl-0.6.9.8
18 ;;; 2 = merged package SB-CONDITIONS into SB-KERNEL around sbcl-0.6.9.8
19
20 ;;; ### remaining work:
21 ;;;
22 ;;; - add more inline operations.
23 ;;; - Breakpoints/debugging info.
24 \f
25 ;;;; stuff to emit noise
26
27 ;;; Note: We use the regular assembler, but we don't use any
28 ;;; ``instructions'' because there is no way to keep our byte-code
29 ;;; instructions separate from the instructions used by the native
30 ;;; backend. Besides, we don't want to do any scheduling or anything
31 ;;; like that, anyway.
32
33 #!-sb-fluid (declaim (inline output-byte))
34 (defun output-byte (segment byte)
35   (declare (type sb!assem:segment segment)
36            (type (unsigned-byte 8) byte))
37   (sb!assem:emit-byte segment byte))
38
39 ;;; Output OPERAND as 1 or 4 bytes, using #xFF as the extend code.
40 (defun output-extended-operand (segment operand)
41   (declare (type (unsigned-byte 24) operand))
42   (cond ((<= operand 254)
43          (output-byte segment operand))
44         (t
45          (output-byte segment #xFF)
46          (output-byte segment (ldb (byte 8 16) operand))
47          (output-byte segment (ldb (byte 8 8) operand))
48          (output-byte segment (ldb (byte 8 0) operand)))))
49
50 ;;; Output a byte, logior'ing in a 4 bit immediate constant. If that
51 ;;; immediate won't fit, then emit it as the next 1-4 bytes.
52 (defun output-byte-with-operand (segment byte operand)
53   (declare (type sb!assem:segment segment)
54            (type (unsigned-byte 8) byte)
55            (type (unsigned-byte 24) operand))
56   (cond ((<= operand 14)
57          (output-byte segment (logior byte operand)))
58         (t
59          (output-byte segment (logior byte 15))
60          (output-extended-operand segment operand)))
61   (values))
62
63 (defun output-label (segment label)
64   (declare (type sb!assem:segment segment)
65            (type sb!assem:label label))
66   (sb!assem:assemble (segment)
67     (sb!assem:emit-label label)))
68
69 ;;; Output a reference to LABEL.
70 (defun output-reference (segment label)
71   (declare (type sb!assem:segment segment)
72            (type sb!assem:label label))
73   (sb!assem:emit-back-patch
74    segment
75    3
76    #'(lambda (segment posn)
77        (declare (type sb!assem:segment segment)
78                 (ignore posn))
79        (let ((target (sb!assem:label-position label)))
80          (assert (<= 0 target (1- (ash 1 24))))
81          (output-byte segment (ldb (byte 8 16) target))
82          (output-byte segment (ldb (byte 8 8) target))
83          (output-byte segment (ldb (byte 8 0) target))))))
84
85 ;;; Output some branch byte-sequence.
86 (defun output-branch (segment kind label)
87   (declare (type sb!assem:segment segment)
88            (type (unsigned-byte 8) kind)
89            (type sb!assem:label label))
90   (sb!assem:emit-chooser
91    segment 4 1
92    #'(lambda (segment posn delta)
93        (when (<= (- (ash 1 7))
94                  (- (sb!assem:label-position label posn delta) posn 2)
95                  (1- (ash 1 7)))
96          (sb!assem:emit-chooser
97           segment 2 1
98           #'(lambda (segment posn delta)
99               (declare (ignore segment) (type index posn delta))
100               (when (zerop (- (sb!assem:label-position label posn delta)
101                               posn 2))
102                 ;; Don't emit anything, because the branch is to the following
103                 ;; instruction.
104                 t))
105           #'(lambda (segment posn)
106               ;; We know that we fit in one byte.
107               (declare (type sb!assem:segment segment)
108                        (type index posn))
109               (output-byte segment (logior kind 1))
110               (output-byte segment
111                            (ldb (byte 8 0)
112                                 (- (sb!assem:label-position label) posn 2)))))
113          t))
114    #'(lambda (segment posn)
115        (declare (type sb!assem:segment segment)
116                 (ignore posn))
117        (let ((target (sb!assem:label-position label)))
118          (assert (<= 0 target (1- (ash 1 24))))
119          (output-byte segment kind)
120          (output-byte segment (ldb (byte 8 16) target))
121          (output-byte segment (ldb (byte 8 8) target))
122          (output-byte segment (ldb (byte 8 0) target))))))
123 \f
124 ;;;; system constants, Xops, and inline functions
125
126 ;;; If (%FDEFINITION-MARKER% . NAME) is a key in the table, then the
127 ;;; corresponding value is the byte code fdefinition.
128 (eval-when (:compile-toplevel :load-toplevel :execute)
129   (defvar *system-constant-codes* (make-hash-table :test 'equal)))
130
131 (eval-when (:compile-toplevel :load-toplevel :execute)
132   (flet ((def-system-constant (index form)
133            (setf (gethash form *system-constant-codes*) index)))
134     (def-system-constant 0 nil)
135     (def-system-constant 1 t)
136     (def-system-constant 2 :start)
137     (def-system-constant 3 :end)
138     (def-system-constant 4 :test)
139     (def-system-constant 5 :count)
140     (def-system-constant 6 :test-not)
141     (def-system-constant 7 :key)
142     (def-system-constant 8 :from-end)
143     (def-system-constant 9 :type)
144     (def-system-constant 10 '(%fdefinition-marker% . error))
145     (def-system-constant 11 '(%fdefinition-marker% . format))
146     (def-system-constant 12 '(%fdefinition-marker% . %typep))
147     (def-system-constant 13 '(%fdefinition-marker% . eql))
148     (def-system-constant 14 '(%fdefinition-marker% . %negate))
149     (def-system-constant 15 '(%fdefinition-marker% . %%defun))
150     (def-system-constant 16 '(%fdefinition-marker% . %%defmacro))
151     (def-system-constant 17 '(%fdefinition-marker% . %%defconstant))
152     (def-system-constant 18 '(%fdefinition-marker% . length))
153     (def-system-constant 19 '(%fdefinition-marker% . equal))
154     (def-system-constant 20 '(%fdefinition-marker% . append))
155     (def-system-constant 21 '(%fdefinition-marker% . reverse))
156     (def-system-constant 22 '(%fdefinition-marker% . nreverse))
157     (def-system-constant 23 '(%fdefinition-marker% . nconc))
158     (def-system-constant 24 '(%fdefinition-marker% . list))
159     (def-system-constant 25 '(%fdefinition-marker% . list*))
160     (def-system-constant 26 '(%fdefinition-marker% . %coerce-name-to-function))
161     (def-system-constant 27 '(%fdefinition-marker% . values-list))))
162
163 (eval-when (#+sb-xc :compile-toplevel :load-toplevel :execute)
164
165 (defparameter *xop-names*
166   '(breakpoint; 0
167     dup; 1
168     type-check; 2
169     fdefn-function-or-lose; 3
170     default-unknown-values; 4
171     push-n-under; 5
172     xop6
173     xop7
174     merge-unknown-values
175     make-closure
176     throw
177     catch
178     breakup
179     return-from
180     tagbody
181     go
182     unwind-protect))
183
184 (defun xop-index-or-lose (name)
185   (or (position name *xop-names* :test #'eq)
186       (error "unknown XOP ~S" name)))
187
188 ) ; EVAL-WHEN
189
190 ;;; FIXME: The hardwired 32 here (found also in (MOD 32) above, and in
191 ;;; the number of bits tested in EXPAND-INTO-INLINES, and perhaps
192 ;;; elsewhere) is ugly. There should be some symbolic constant for the
193 ;;; number of bits devoted to coding byte-inline functions.
194 (eval-when (:compile-toplevel :load-toplevel :execute)
195
196   (defstruct inline-function-info
197     ;; the name of the function that we convert into calls to this
198     (function (required-argument) :type symbol)
199     ;; the name of the function that the interpreter should call to
200     ;; implement this. This may not be the same as the FUNCTION slot
201     ;; value if extra safety checks are required.
202     (interpreter-function (required-argument) :type symbol)
203     ;; the inline operation number, i.e. the byte value actually
204     ;; written into byte-compiled code
205     (number (required-argument) :type (mod 32))
206     ;; the type that calls must satisfy
207     (type (required-argument) :type function-type)
208     ;; Can we skip type checking of the arguments?
209     (safe (required-argument) :type boolean))
210
211   (defparameter *inline-functions* (make-array 32 :initial-element nil))
212   (defparameter *inline-function-table* (make-hash-table :test 'eq))
213   (let ((number 0))
214     (dolist (stuff
215              '((+ (fixnum fixnum) fixnum)
216                (- (fixnum fixnum) fixnum)
217                (make-value-cell (t) t)
218                (value-cell-ref (t) t)
219                (value-cell-setf (t t) (values))
220                (symbol-value (symbol) t
221                              :interpreter-function %byte-symbol-value)
222                (setf-symbol-value (t symbol) (values))
223                (%byte-special-bind (t symbol) (values))
224                (%byte-special-unbind () (values))
225                (cons-unique-tag () t)   ; obsolete...
226                (%negate (fixnum) fixnum)
227                (< (fixnum fixnum) t)
228                (> (fixnum fixnum) t)
229                (car (t) t :interpreter-function %byte-car :safe t)
230                (cdr (t) t :interpreter-function %byte-cdr :safe t)
231                (length (list) t)
232                (cons (t t) t)
233                (list (t t) t)
234                (list* (t t t) t)
235                (%instance-ref (t t) t)
236                (%setf-instance-ref (t t t) (values))))
237       (destructuring-bind
238           (name arg-types result-type
239                 &key (interpreter-function name) alias safe)
240           stuff
241         (let ((info
242                (make-inline-function-info
243                 :function name
244                 :number number
245                 :interpreter-function interpreter-function
246                 :type (specifier-type `(function ,arg-types ,result-type))
247                 :safe safe)))
248           (setf (svref *inline-functions* number) info)
249           (setf (gethash name *inline-function-table*) info))
250         (unless alias (incf number))))))
251
252 (defun inline-function-number-or-lose (function)
253   (let ((info (gethash function *inline-function-table*)))
254     (if info
255         (inline-function-info-number info)
256         (error "unknown inline function: ~S" function))))
257 \f
258 ;;;; transforms which are specific to byte code
259
260 ;;; It appears that the idea here is that in byte code, EQ is more
261 ;;; efficient than CHAR=. -- WHN 199910
262
263 (deftransform eql ((x y) ((or fixnum character) (or fixnum character))
264                    * :when :byte)
265   '(eq x y))
266
267 (deftransform char= ((x y) * * :when :byte)
268   '(eq x y))
269 \f
270 ;;;; annotations hung off the IR1 while compiling
271
272 (defstruct byte-component-info
273   (constants (make-array 10 :adjustable t :fill-pointer 0)))
274
275 (defstruct byte-lambda-info
276   (label nil :type (or null label))
277   (stack-size 0 :type index)
278   ;; FIXME: should be INTERESTING-P T :TYPE BOOLEAN
279   (interesting t :type (member t nil)))
280
281 (defun block-interesting (block)
282   (byte-lambda-info-interesting (lambda-info (block-home-lambda block))))
283
284 (defstruct byte-lambda-var-info
285   (argp nil :type (member t nil))
286   (offset 0 :type index))
287
288 (defstruct byte-nlx-info
289   (stack-slot nil :type (or null index))
290   (label (sb!assem:gen-label) :type sb!assem:label)
291   (duplicate nil :type (member t nil)))
292
293 (defstruct (byte-block-info
294             (:include block-annotation)
295             (:constructor make-byte-block-info
296                           (block &key produces produces-sset consumes
297                             total-consumes nlx-entries nlx-entry-p)))
298   (label (sb!assem:gen-label) :type sb!assem:label)
299   ;; A list of the CONTINUATIONs describing values that this block
300   ;; pushes onto the stack. Note: PRODUCES and CONSUMES can contain
301   ;; the keyword :NLX-ENTRY marking the place on the stack where a
302   ;; non-local-exit frame is added or removed. Since breaking up a NLX
303   ;; restores the stack, we don't have to about (and in fact must not)
304   ;; discard values underneath a :NLX-ENTRY marker evern though they
305   ;; appear to be dead (since they might not be.)
306   (produces nil :type list)
307   ;; An SSET of the produces for faster set manipulations. The
308   ;; elements are the BYTE-CONTINUATION-INFO objects. :NLX-ENTRY
309   ;; markers are not represented.
310   (produces-sset (make-sset) :type sset)
311   ;; A list of the continuations that this block pops from the stack.
312   ;; See PRODUCES.
313   (consumes nil :type list)
314   ;; The transitive closure of what this block and all its successors
315   ;; consume. After stack-analysis, that is.
316   (total-consumes (make-sset) :type sset)
317   ;; Set to T whenever the consumes lists of a successor changes and
318   ;; the block is queued for re-analysis so we can easily avoid
319   ;; queueing the same block several times.
320   (already-queued nil :type (member t nil))
321   ;; The continuations and :NLX-ENTRY markers on the stack (in order)
322   ;; when this block starts.
323   (start-stack :unknown :type (or (member :unknown) list))
324   ;; The continuations and :NLX-ENTRY markers on the stack (in order)
325   ;; when this block ends.
326   (end-stack nil :type list)
327   ;; List of ((nlx-info*) produces consumes) for each ENTRY in this
328   ;; block that is a NLX target.
329   (nlx-entries nil :type list)
330   ;; T if this is an %nlx-entry point, and we shouldn't just assume we
331   ;; know what is going to be on the stack.
332   (nlx-entry-p nil :type (member t nil)))
333
334 (defprinter (byte-block-info)
335   block)
336
337 (defstruct (byte-continuation-info
338             (:include sset-element)
339             (:constructor make-byte-continuation-info
340                           (continuation results placeholders)))
341   (continuation (required-argument) :type continuation)
342   (results (required-argument)
343            :type (or (member :fdefinition :eq-test :unknown) index))
344   ;; If the DEST is a local non-MV call, then we may need to push some
345   ;; number of placeholder args corresponding to deleted
346   ;; (unreferenced) args. If PLACEHOLDERS /= 0, then RESULTS is
347   ;; PLACEHOLDERS + 1.
348   (placeholders (required-argument) :type index))
349
350 (defprinter (byte-continuation-info)
351   continuation
352   results
353   (placeholders :test (/= placeholders 0)))
354 \f
355 ;;;; Annotate the IR1.
356
357 (defun annotate-continuation (cont results &optional (placeholders 0))
358   ;; For some reason, DO-NODES does the same return node multiple
359   ;; times, which causes ANNOTATE-CONTINUATION to be called multiple
360   ;; times on the same continuation. So we can't assert that we
361   ;; haven't done it.
362   #+nil
363   (assert (null (continuation-info cont)))
364   (setf (continuation-info cont)
365         (make-byte-continuation-info cont results placeholders))
366   (values))
367
368 (defun annotate-set (set)
369   ;; Annotate the value for one value.
370   (annotate-continuation (set-value set) 1))
371
372 ;;; We do different stack magic for non-MV and MV calls to figure out
373 ;;; how many values should be pushed during compilation of each arg.
374 ;;;
375 ;;; Since byte functions are directly caller by the interpreter (there
376 ;;; is no XEP), and it doesn't know which args are actually used, byte
377 ;;; functions must allow unused args to be passed. But this creates a
378 ;;; problem with local calls, because these unused args would not
379 ;;; otherwise be pushed (since the continuation has been deleted.) So,
380 ;;; in this function, we count up placeholders for any unused args
381 ;;; contiguously preceding this one. These placeholders are inserted
382 ;;; under the referenced arg by CHECKED-CANONICALIZE-VALUES.
383 ;;;
384 ;;; With MV calls, we try to figure out how many values are actually
385 ;;; generated. We allow initial args to supply a fixed number of
386 ;;; values, but everything after the first :unknown arg must also be
387 ;;; unknown. This picks off most of the standard uses (i.e. calls to
388 ;;; apply), but still is easy to implement.
389 (defun annotate-basic-combination-args (call)
390   (declare (type basic-combination call))
391   (etypecase call
392     (combination
393      (if (and (eq (basic-combination-kind call) :local)
394               (member (functional-kind (combination-lambda call))
395                       '(nil :optional :cleanup)))
396          (let ((placeholders 0))
397            (declare (type index placeholders))
398            (dolist (arg (combination-args call))
399              (cond (arg
400                     (annotate-continuation arg (1+ placeholders) placeholders)
401                     (setq placeholders 0))
402                    (t
403                     (incf placeholders)))))
404          (dolist (arg (combination-args call))
405            (when arg
406              (annotate-continuation arg 1)))))
407     (mv-combination
408      (labels
409          ((allow-fixed (remaining)
410             (when remaining
411               (let* ((cont (car remaining))
412                      (values (nth-value 1
413                                         (values-types
414                                          (continuation-derived-type cont)))))
415                 (cond ((eq values :unknown)
416                        (force-to-unknown remaining))
417                       (t
418                        (annotate-continuation cont values)
419                        (allow-fixed (cdr remaining)))))))
420           (force-to-unknown (remaining)
421             (when remaining
422               (let ((cont (car remaining)))
423                 (when cont
424                   (annotate-continuation cont :unknown)))
425               (force-to-unknown (cdr remaining)))))
426        (allow-fixed (mv-combination-args call)))))
427   (values))
428
429 (defun annotate-local-call (call)
430   (cond ((mv-combination-p call)
431          (annotate-continuation
432           (first (basic-combination-args call))
433           (length (lambda-vars (combination-lambda call)))))
434         (t
435          (annotate-basic-combination-args call)
436          (when (member (functional-kind (combination-lambda call))
437                        '(nil :optional :cleanup))
438            (dolist (arg (basic-combination-args call))
439              (when arg
440                (setf (continuation-%type-check arg) nil))))))
441   (annotate-continuation (basic-combination-fun call) 0)
442   (when (node-tail-p call)
443     (set-tail-local-call-successor call)))
444
445 ;;; Annotate the values for any :full combination. This includes
446 ;;; inline functions, multiple value calls & throw. If a real full
447 ;;; call or a safe inline operation, then clear any type-check
448 ;;; annotations. When we are done, remove jump to return for tail
449 ;;; calls.
450 ;;;
451 ;;; Also, we annotate slot accessors as inline if no type check is
452 ;;; needed and (for setters) no value needs to be left on the stack.
453 (defun annotate-full-call (call)
454   (let* ((fun (basic-combination-fun call))
455          (args (basic-combination-args call))
456          (name (continuation-function-name fun))
457          (info (gethash name *inline-function-table*)))
458     (flet ((annotate-args ()
459              (annotate-basic-combination-args call)
460              (dolist (arg args)
461                (when (continuation-type-check arg)
462                  (setf (continuation-%type-check arg) :deleted)))
463              (annotate-continuation
464               fun
465               (if (continuation-function-name fun) :fdefinition 1))))
466       (cond ((mv-combination-p call)
467              (cond ((eq name '%throw)
468                     (assert (= (length args) 2))
469                     (annotate-continuation (first args) 1)
470                     (annotate-continuation (second args) :unknown)
471                     (setf (node-tail-p call) nil)
472                     (annotate-continuation fun 0))
473                    (t
474                     (annotate-args))))
475             ((and info
476                   (valid-function-use call (inline-function-info-type info)))
477              (annotate-basic-combination-args call)
478              (setf (node-tail-p call) nil)
479              (setf (basic-combination-info call) info)
480              (annotate-continuation fun 0)
481              (when (inline-function-info-safe info)
482                (dolist (arg args)
483                  (when (continuation-type-check arg)
484                    (setf (continuation-%type-check arg) :deleted)))))
485             ((and name
486                   (let ((leaf (ref-leaf (continuation-use fun))))
487                     (and (slot-accessor-p leaf)
488                          (or (policy call (zerop safety))
489                              (not (find 't args
490                                         :key #'continuation-type-check)))
491                          (if (consp name)
492                              (not (continuation-dest (node-cont call)))
493                              t))))
494              (setf (basic-combination-info call)
495                    (gethash (if (consp name) '%setf-instance-ref '%instance-ref)
496                             *inline-function-table*))
497              (setf (node-tail-p call) nil)
498              (annotate-continuation fun 0)
499              (annotate-basic-combination-args call))
500             (t
501              (annotate-args)))))
502
503   ;; If this is (still) a tail-call, then blow away the return.
504   (when (node-tail-p call)
505     (node-ends-block call)
506     (let ((block (node-block call)))
507       (unlink-blocks block (first (block-succ block)))
508       (link-blocks block (component-tail (block-component block)))))
509
510   (values))
511
512 (defun annotate-known-call (call)
513   (annotate-basic-combination-args call)
514   (setf (node-tail-p call) nil)
515   (annotate-continuation (basic-combination-fun call) 0)
516   t)
517
518 (defun annotate-basic-combination (call)
519   ;; Annotate the function.
520   (let ((kind (basic-combination-kind call)))
521     (case kind
522       (:local
523        (annotate-local-call call))
524       (:full
525        (annotate-full-call call))
526       (:error
527        (setf (basic-combination-kind call) :full)
528        (annotate-full-call call))
529       (t
530        (unless (and (function-info-byte-compile kind)
531                     (funcall (or (function-info-byte-annotate kind)
532                                  #'annotate-known-call)
533                              call))
534          (setf (basic-combination-kind call) :full)
535          (annotate-full-call call)))))
536
537   (values))
538
539 (defun annotate-if (if)
540   ;; Annotate the test.
541   (let* ((cont (if-test if))
542          (use (continuation-use cont)))
543     (annotate-continuation
544      cont
545      (if (and (combination-p use)
546               (eq (continuation-function-name (combination-fun use)) 'eq)
547               (= (length (combination-args use)) 2))
548          ;; If the test is a call to EQ, then we can use branch-if-eq
549          ;; so don't need to actually funcall the test.
550          :eq-test
551          ;; Otherwise, funcall the test for 1 value.
552          1))))
553
554 (defun annotate-return (return)
555   (let ((cont (return-result return)))
556     (annotate-continuation
557      cont
558      (nth-value 1 (values-types (continuation-derived-type cont))))))
559
560 (defun annotate-exit (exit)
561   (let ((cont (exit-value exit)))
562     (when cont
563       (annotate-continuation cont :unknown))))
564
565 (defun annotate-block (block)
566   (do-nodes (node cont block)
567     (etypecase node
568       (bind)
569       (ref)
570       (cset (annotate-set node))
571       (basic-combination (annotate-basic-combination node))
572       (cif (annotate-if node))
573       (creturn (annotate-return node))
574       (entry)
575       (exit (annotate-exit node))))
576   (values))
577
578 (defun annotate-ir1 (component)
579   (do-blocks (block component)
580     (when (block-interesting block)
581       (annotate-block block)))
582   (values))
583 \f
584 ;;;; stack analysis
585
586 (defvar *byte-continuation-counter*)
587
588 ;;; Scan the nodes in BLOCK and compute the information that we will
589 ;;; need to do flow analysis and our stack simulation walk. We simulate
590 ;;; the stack within the block, reducing it to ordered lists
591 ;;; representing the values we remove from the top of the stack and
592 ;;; place on the stack (not considering values that are produced and
593 ;;; consumed within the block.) A NLX entry point is considered to
594 ;;; push a :NLX-ENTRY marker (can be though of as the run-time catch
595 ;;; frame.)
596 (defun compute-produces-and-consumes (block)
597   (let ((stack nil)
598         (consumes nil)
599         (total-consumes (make-sset))
600         (nlx-entries nil)
601         (nlx-entry-p nil))
602     (labels ((interesting (cont)
603                (and cont
604                     (let ((info (continuation-info cont)))
605                       (and info
606                            (not (member (byte-continuation-info-results info)
607                                         '(0 :eq-test)))))))
608              (consume (cont)
609                (cond ((not (or (eq cont :nlx-entry) (interesting cont))))
610                      (stack
611                       (assert (eq (car stack) cont))
612                       (pop stack))
613                      (t
614                       (adjoin-cont cont total-consumes)
615                       (push cont consumes))))
616              (adjoin-cont (cont sset)
617                (unless (eq cont :nlx-entry)
618                  (let ((info (continuation-info cont)))
619                    (unless (byte-continuation-info-number info)
620                      (setf (byte-continuation-info-number info)
621                            (incf *byte-continuation-counter*)))
622                    (sset-adjoin info sset)))))
623       (do-nodes (node cont block)
624         (etypecase node
625           (bind)
626           (ref)
627           (cset
628            (consume (set-value node)))
629           (basic-combination
630            (dolist (arg (reverse (basic-combination-args node)))
631              (when arg
632                (consume arg)))
633            (consume (basic-combination-fun node))
634            (case (continuation-function-name (basic-combination-fun node))
635              (%nlx-entry
636               (let ((nlx-info (continuation-value
637                                (first (basic-combination-args node)))))
638                 (ecase (cleanup-kind (nlx-info-cleanup nlx-info))
639                   ((:catch :unwind-protect)
640                    (consume :nlx-entry))
641                   ;; If for a lexical exit, we will see a breakup later, so
642                   ;; don't consume :NLX-ENTRY now.
643                   (:tagbody)
644                   (:block
645                    (let ((cont (nlx-info-continuation nlx-info)))
646                      (when (interesting cont)
647                        (push cont stack))))))
648               (setf nlx-entry-p t))
649              (%lexical-exit-breakup
650               (unless (byte-nlx-info-duplicate
651                        (nlx-info-info
652                         (continuation-value
653                          (first (basic-combination-args node)))))
654                 (consume :nlx-entry)))
655              ((%catch-breakup %unwind-protect-breakup)
656               (consume :nlx-entry))))
657           (cif
658            (consume (if-test node)))
659           (creturn
660            (consume (return-result node)))
661           (entry
662            (let* ((cup (entry-cleanup node))
663                   (nlx-info (cleanup-nlx-info cup)))
664              (when nlx-info
665                (push :nlx-entry stack)
666                (push (list nlx-info stack (reverse consumes))
667                      nlx-entries))))
668           (exit
669            (when (exit-value node)
670              (consume (exit-value node)))))
671         (when (and (not (exit-p node)) (interesting cont))
672           (push cont stack)))
673
674       (setf (block-info block)
675             (make-byte-block-info
676              block
677              :produces stack
678              :produces-sset (let ((res (make-sset)))
679                               (dolist (product stack)
680                                 (adjoin-cont product res))
681                               res)
682              :consumes (reverse consumes)
683              :total-consumes total-consumes
684              :nlx-entries nlx-entries
685              :nlx-entry-p nlx-entry-p))))
686
687   (values))
688
689 (defun walk-successors (block stack)
690   (let ((tail (component-tail (block-component block))))
691     (dolist (succ (block-succ block))
692       (unless (or (eq succ tail)
693                   (not (block-interesting succ))
694                   (byte-block-info-nlx-entry-p (block-info succ)))
695         (walk-block succ block stack)))))
696
697 ;;; Take a stack and a consumes list, and remove the appropriate
698 ;;; stuff. When we consume a :NLX-ENTRY, we just remove the top
699 ;;; marker, and leave any values on top intact. This represents the
700 ;;; desired effect of %CATCH-BREAKUP, etc., which don't affect any
701 ;;; values on the stack.
702 (defun consume-stuff (stack stuff)
703   (let ((new-stack stack))
704     (dolist (cont stuff)
705       (cond ((eq cont :nlx-entry)
706              (assert (find :nlx-entry new-stack))
707              (setq new-stack (remove :nlx-entry new-stack :count 1)))
708             (t
709              (assert (eq (car new-stack) cont))
710              (pop new-stack))))
711     new-stack))
712
713 ;;; NLX-INFOS is the list of NLX-INFO structures for this ENTRY note.
714 ;;; CONSUME and PRODUCE are the values from outside this block that
715 ;;; were consumed and produced by this block before the ENTRY node.
716 ;;; STACK is the globally simulated stack at the start of this block.
717 (defun walk-nlx-entry (nlx-infos stack produce consume)
718   (let ((stack (consume-stuff stack consume)))
719     (dolist (nlx-info nlx-infos)
720       (walk-block (nlx-info-target nlx-info) nil (append produce stack))))
721   (values))
722
723 ;;; Simulate the stack across block boundaries, discarding any values
724 ;;; that are dead. A :NLX-ENTRY marker prevents values live at a NLX
725 ;;; entry point from being discarded prematurely.
726 (defun walk-block (block pred stack)
727   ;; Pop everything off of stack that isn't live.
728   (let* ((info (block-info block))
729          (live (byte-block-info-total-consumes info)))
730     (collect ((pops))
731       (let ((fixed 0))
732         (flet ((flush-fixed ()
733                  (unless (zerop fixed)
734                    (pops `(%byte-pop-stack ,fixed))
735                    (setf fixed 0))))
736           (loop
737             (unless stack
738               (return))
739             (let ((cont (car stack)))
740               (when (or (eq cont :nlx-entry)
741                         (sset-member (continuation-info cont) live))
742                 (return))
743               (pop stack)
744               (let ((results
745                      (byte-continuation-info-results
746                       (continuation-info cont))))
747                 (case results
748                   (:unknown
749                    (flush-fixed)
750                    (pops `(%byte-pop-stack 0)))
751                   (:fdefinition
752                    (incf fixed))
753                   (t
754                    (incf fixed results))))))
755           (flush-fixed)))
756       (when (pops)
757         (assert pred)
758         (let ((cleanup-block
759                (insert-cleanup-code pred block
760                                     (continuation-next (block-start block))
761                                     `(progn ,@(pops)))))
762           (annotate-block cleanup-block))))
763
764     (cond ((eq (byte-block-info-start-stack info) :unknown)
765            ;; Record what the stack looked like at the start of this block.
766            (setf (byte-block-info-start-stack info) stack)
767            ;; Process any nlx entries that build off of our stack.
768            (dolist (stuff (byte-block-info-nlx-entries info))
769              (walk-nlx-entry (first stuff) stack (second stuff) (third stuff)))
770            ;; Remove whatever we consume.
771            (setq stack (consume-stuff stack (byte-block-info-consumes info)))
772            ;; Add whatever we produce.
773            (setf stack (append (byte-block-info-produces info) stack))
774            (setf (byte-block-info-end-stack info) stack)
775            ;; Pass that on to all our successors.
776            (walk-successors block stack))
777           (t
778            ;; We have already processed the successors of this block. Just
779            ;; make sure we thing the stack is the same now as before.
780            (assert (equal (byte-block-info-start-stack info) stack)))))
781   (values))
782
783 ;;; Do lifetime flow analysis on values pushed on the stack, then call
784 ;;; do the stack simulation walk to discard dead values. In addition
785 ;;; to considering the obvious inputs from a block's successors, we
786 ;;; must also consider %NLX-ENTRY targets to be successors in order to
787 ;;; ensure that any values only used in the NLX entry stay alive until
788 ;;; we reach the mess-up node. After then, we can keep the values from
789 ;;; being discarded by placing a marker on the simulated stack.
790 (defun byte-stack-analyze (component)
791   (let ((head nil))
792     (let ((*byte-continuation-counter* 0))
793       (do-blocks (block component)
794         (when (block-interesting block)
795           (compute-produces-and-consumes block)
796           (push block head)
797           (setf (byte-block-info-already-queued (block-info block)) t))))
798     (let ((tail (last head)))
799       (labels ((maybe-enqueue (block)
800                  (when (block-interesting block)
801                    (let ((info (block-info block)))
802                      (unless (byte-block-info-already-queued info)
803                        (setf (byte-block-info-already-queued info) t)
804                        (let ((new (list block)))
805                          (if head
806                              (setf (cdr tail) new)
807                              (setf head new))
808                          (setf tail new))))))
809                (maybe-enqueue-predecessors (block)
810                  (when (byte-block-info-nlx-entry-p (block-info block))
811                    (maybe-enqueue
812                     (node-block
813                      (cleanup-mess-up
814                       (nlx-info-cleanup
815                        (find block
816                              (environment-nlx-info (block-environment block))
817                              :key #'nlx-info-target))))))
818
819                  (dolist (pred (block-pred block))
820                    (unless (eq pred (component-head (block-component block)))
821                      (maybe-enqueue pred)))))
822         (loop
823           (unless head
824             (return))
825           (let* ((block (pop head))
826                  (info (block-info block))
827                  (total-consumes (byte-block-info-total-consumes info))
828                  (produces-sset (byte-block-info-produces-sset info))
829                  (did-anything nil))
830             (setf (byte-block-info-already-queued info) nil)
831             (dolist (succ (block-succ block))
832               (unless (eq succ (component-tail component))
833                 (let ((succ-info (block-info succ)))
834                   (when (sset-union-of-difference
835                          total-consumes
836                          (byte-block-info-total-consumes succ-info)
837                          produces-sset)
838                     (setf did-anything t)))))
839             (dolist (nlx-list (byte-block-info-nlx-entries info))
840               (dolist (nlx-info (first nlx-list))
841                 (when (sset-union-of-difference
842                        total-consumes
843                        (byte-block-info-total-consumes
844                         (block-info
845                          (nlx-info-target nlx-info)))
846                        produces-sset)
847                   (setf did-anything t))))
848             (when did-anything
849               (maybe-enqueue-predecessors block)))))))
850
851   (walk-successors (component-head component) nil)
852   (values))
853 \f
854 ;;;; Actually generate the byte code.
855
856 (defvar *byte-component-info*)
857
858 ;;; FIXME: These might as well be generated with DEFENUM, right?
859 ;;; It would also be nice to give them less ambiguous names, perhaps
860 ;;; with a "BYTEOP-" prefix instead of "BYTE-".
861 (defconstant byte-push-local           #b00000000)
862 (defconstant byte-push-arg             #b00010000)
863 (defconstant byte-push-constant        #b00100000)
864 (defconstant byte-push-system-constant #b00110000)
865 (defconstant byte-push-int             #b01000000)
866 (defconstant byte-push-neg-int         #b01010000)
867 (defconstant byte-pop-local            #b01100000)
868 (defconstant byte-pop-n                #b01110000)
869 (defconstant byte-call                 #b10000000)
870 (defconstant byte-tail-call            #b10010000)
871 (defconstant byte-multiple-call        #b10100000)
872 (defconstant byte-named                #b00001000)
873 (defconstant byte-local-call           #b10110000)
874 (defconstant byte-local-tail-call      #b10111000)
875 (defconstant byte-local-multiple-call  #b11000000)
876 (defconstant byte-return               #b11001000)
877 (defconstant byte-branch-always        #b11010000)
878 (defconstant byte-branch-if-true       #b11010010)
879 (defconstant byte-branch-if-false      #b11010100)
880 (defconstant byte-branch-if-eq         #b11010110)
881 (defconstant byte-xop                  #b11011000)
882 (defconstant byte-inline-function      #b11100000)
883
884 (defun output-push-int (segment int)
885   (declare (type sb!assem:segment segment)
886            (type (integer #.(- (ash 1 24)) #.(1- (ash 1 24)))))
887   (if (minusp int)
888       (output-byte-with-operand segment byte-push-neg-int (- (1+ int)))
889       (output-byte-with-operand segment byte-push-int int)))
890
891 (defun output-push-constant-leaf (segment constant)
892   (declare (type sb!assem:segment segment)
893            (type constant constant))
894   (let ((info (constant-info constant)))
895     (if info
896         (output-byte-with-operand segment
897                                   (ecase (car info)
898                                     (:system-constant
899                                      byte-push-system-constant)
900                                     (:local-constant
901                                      byte-push-constant))
902                                   (cdr info))
903         (let ((const (constant-value constant)))
904           (if (and (integerp const) (< (- (ash 1 24)) const (ash 1 24)))
905               ;; It can be represented as an immediate.
906               (output-push-int segment const)
907               ;; We need to store it in the constants pool.
908               (let* ((posn
909                       (unless (and (consp const)
910                                    (eq (car const) '%fdefinition-marker%))
911                         (gethash const *system-constant-codes*)))
912                      (new-info (if posn
913                                    (cons :system-constant posn)
914                                    (cons :local-constant
915                                          (vector-push-extend
916                                           constant
917                                           (byte-component-info-constants
918                                            *byte-component-info*))))))
919                 (setf (constant-info constant) new-info)
920                 (output-push-constant-leaf segment constant)))))))
921
922 (defun output-push-constant (segment value)
923   (if (and (integerp value)
924            (< (- (ash 1 24)) value (ash 1 24)))
925       (output-push-int segment value)
926       (output-push-constant-leaf segment (find-constant value))))
927
928 ;;; Return the offset of a load-time constant in the constant pool,
929 ;;; adding it if absent.
930 (defun byte-load-time-constant-index (kind datum)
931   (let ((constants (byte-component-info-constants *byte-component-info*)))
932     (or (position-if #'(lambda (x)
933                          (and (consp x)
934                               (eq (car x) kind)
935                               (typecase datum
936                                 (cons (equal (cdr x) datum))
937                                 (ctype (type= (cdr x) datum))
938                                 (t
939                                  (eq (cdr x) datum)))))
940                      constants)
941         (vector-push-extend (cons kind datum) constants))))
942
943 (defun output-push-load-time-constant (segment kind datum)
944   (output-byte-with-operand segment byte-push-constant
945                             (byte-load-time-constant-index kind datum))
946   (values))
947
948 (defun output-do-inline-function (segment function)
949   ;; Note: we don't annotate this as a call site, because it is used
950   ;; for internal stuff. Functions that get inlined have code
951   ;; locations added byte generate-byte-code-for-full-call below.
952   (output-byte segment
953                (logior byte-inline-function
954                        (inline-function-number-or-lose function))))
955
956 (defun output-do-xop (segment xop)
957   (let ((index (xop-index-or-lose xop)))
958     (cond ((< index 7)
959            (output-byte segment (logior byte-xop index)))
960           (t
961            (output-byte segment (logior byte-xop 7))
962            (output-byte segment index)))))
963
964 (defun closure-position (var env)
965   (or (position var (environment-closure env))
966       (error "Can't find ~S" var)))
967
968 (defun output-ref-lambda-var (segment var env
969                                      &optional (indirect-value-cells t))
970   (declare (type sb!assem:segment segment)
971            (type lambda-var var)
972            (type environment env))
973   (if (eq (lambda-environment (lambda-var-home var)) env)
974       (let ((info (leaf-info var)))
975         (output-byte-with-operand segment
976                                   (if (byte-lambda-var-info-argp info)
977                                       byte-push-arg
978                                       byte-push-local)
979                                   (byte-lambda-var-info-offset info)))
980       (output-byte-with-operand segment
981                                 byte-push-arg
982                                 (closure-position var env)))
983   (when (and indirect-value-cells (lambda-var-indirect var))
984     (output-do-inline-function segment 'value-cell-ref)))
985
986 (defun output-ref-nlx-info (segment info env)
987   (if (eq (node-environment (cleanup-mess-up (nlx-info-cleanup info))) env)
988       (output-byte-with-operand segment
989                                 byte-push-local
990                                 (byte-nlx-info-stack-slot
991                                  (nlx-info-info info)))
992       (output-byte-with-operand segment
993                                 byte-push-arg
994                                 (closure-position info env))))
995
996 (defun output-set-lambda-var (segment var env &optional make-value-cells)
997   (declare (type sb!assem:segment segment)
998            (type lambda-var var)
999            (type environment env))
1000   (let ((indirect (lambda-var-indirect var)))
1001     (cond ((not (eq (lambda-environment (lambda-var-home var)) env))
1002            ;; This is not this guy's home environment. So we need to
1003            ;; get it the value cell out of the closure, and fill it in.
1004            (assert indirect)
1005            (assert (not make-value-cells))
1006            (output-byte-with-operand segment byte-push-arg
1007                                      (closure-position var env))
1008            (output-do-inline-function segment 'value-cell-setf))
1009           (t
1010            (let* ((pushp (and indirect (not make-value-cells)))
1011                   (byte-code (if pushp byte-push-local byte-pop-local))
1012                   (info (leaf-info var)))
1013              (assert (not (byte-lambda-var-info-argp info)))
1014              (when (and indirect make-value-cells)
1015                ;; Replace the stack top with a value cell holding the
1016                ;; stack top.
1017                (output-do-inline-function segment 'make-value-cell))
1018              (output-byte-with-operand segment byte-code
1019                                        (byte-lambda-var-info-offset info))
1020              (when pushp
1021                (output-do-inline-function segment 'value-cell-setf)))))))
1022
1023 ;;; Output whatever noise is necessary to canonicalize the values on
1024 ;;; the top of the stack. DESIRED is the number we want, and SUPPLIED
1025 ;;; is the number we have. Either push NIL or pop-n to make them
1026 ;;; balanced. Note: either desired or supplied can be :unknown, in
1027 ;;; which case it means use the ``unknown-values'' convention (which
1028 ;;; is the stack values followed by the number of values).
1029 (defun canonicalize-values (segment desired supplied)
1030   (declare (type sb!assem:segment segment)
1031            (type (or (member :unknown) index) desired supplied))
1032   (cond ((eq desired :unknown)
1033          (unless (eq supplied :unknown)
1034            (output-byte-with-operand segment byte-push-int supplied)))
1035         ((eq supplied :unknown)
1036          (unless (eq desired :unknown)
1037            (output-push-int segment desired)
1038            (output-do-xop segment 'default-unknown-values)))
1039         ((< supplied desired)
1040          (dotimes (i (- desired supplied))
1041            (output-push-constant segment nil)))
1042         ((> supplied desired)
1043          (output-byte-with-operand segment byte-pop-n (- supplied desired))))
1044   (values))
1045
1046 (defparameter *byte-type-weakenings*
1047   (mapcar #'specifier-type
1048           '(fixnum single-float double-float simple-vector simple-bit-vector
1049                    bit-vector)))
1050
1051 ;;; Emit byte code to check that the value on top of the stack is of
1052 ;;; the specified TYPE. NODE is used for policy information. We weaken
1053 ;;; or entirely omit the type check whether speed is more important
1054 ;;; than safety.
1055 (defun byte-generate-type-check (segment type node)
1056   (declare (type ctype type) (type node node))
1057   (unless (or (policy node (zerop safety))
1058               (csubtypep *universal-type* type))
1059     (let ((type (if (policy node (> speed safety))
1060                     (dolist (super *byte-type-weakenings* type)
1061                       (when (csubtypep type super) (return super)))
1062                     type)))
1063       (output-do-xop segment 'type-check)
1064       (output-extended-operand
1065        segment
1066        (byte-load-time-constant-index :type-predicate type)))))
1067
1068 ;;; This function is used when we are generating code which delivers
1069 ;;; values to a continuation. If this continuation needs a type check,
1070 ;;; and has a single value, then we do a type check. We also
1071 ;;; CANONICALIZE-VALUES for the continuation's desired number of
1072 ;;; values (w/o the placeholders.)
1073 ;;;
1074 ;;; Somewhat unrelatedly, we also push placeholders for deleted
1075 ;;; arguments to local calls. Although we check first, the actual
1076 ;;; PUSH-N-UNDER is done afterward, since then the single value we
1077 ;;; want is stack top.
1078 (defun checked-canonicalize-values (segment cont supplied)
1079   (let ((info (continuation-info cont)))
1080     (if info
1081         (let ((desired (byte-continuation-info-results info))
1082               (placeholders (byte-continuation-info-placeholders info)))
1083           (unless (zerop placeholders)
1084             (assert (eql desired (1+ placeholders)))
1085             (setq desired 1))
1086
1087           (flet ((do-check ()
1088                    (byte-generate-type-check
1089                     segment
1090                     (single-value-type (continuation-asserted-type cont))
1091                     (continuation-dest cont))))
1092             (cond
1093              ((member (continuation-type-check cont) '(nil :deleted))
1094               (canonicalize-values segment desired supplied))
1095              ((eql supplied 1)
1096               (do-check)
1097               (canonicalize-values segment desired supplied))
1098              ((eql desired 1)
1099               (canonicalize-values segment desired supplied)
1100               (do-check))
1101              (t
1102               (canonicalize-values segment desired supplied))))
1103
1104           (unless (zerop placeholders)
1105             (output-do-xop segment 'push-n-under)
1106             (output-extended-operand segment placeholders)))
1107
1108         (canonicalize-values segment 0 supplied))))
1109
1110 ;;; Emit prologue for non-LET functions. Assigned arguments must be
1111 ;;; copied into locals, and argument type checking may need to be done.
1112 (defun generate-byte-code-for-bind (segment bind cont)
1113   (declare (type sb!assem:segment segment) (type bind bind)
1114            (ignore cont))
1115   (let ((lambda (bind-lambda bind))
1116         (env (node-environment bind)))
1117     (ecase (lambda-kind lambda)
1118       ((nil :top-level :escape :cleanup :optional)
1119        (let* ((info (lambda-info lambda))
1120               (type-check (policy (lambda-bind lambda) (not (zerop safety))))
1121               (frame-size (byte-lambda-info-stack-size info)))
1122          (cond ((< frame-size (* 255 2))
1123                 (output-byte segment (ceiling frame-size 2)))
1124                (t
1125                 (output-byte segment 255)
1126                 (output-byte segment (ldb (byte 8 16) frame-size))
1127                 (output-byte segment (ldb (byte 8 8) frame-size))
1128                 (output-byte segment (ldb (byte 8 0) frame-size))))
1129
1130          (do ((argnum (1- (+ (length (lambda-vars lambda))
1131                              (length (environment-closure
1132                                       (lambda-environment lambda)))))
1133                       (1- argnum))
1134               (vars (lambda-vars lambda) (cdr vars))
1135               (pops 0))
1136              ((null vars)
1137               (unless (zerop pops)
1138                 (output-byte-with-operand segment byte-pop-n pops)))
1139            (declare (fixnum argnum pops))
1140            (let* ((var (car vars))
1141                   (info (lambda-var-info var))
1142                   (type (leaf-type var)))
1143              (cond ((not info))
1144                    ((byte-lambda-var-info-argp info)
1145                     (when (and type-check
1146                                (not (csubtypep *universal-type* type)))
1147                       (output-byte-with-operand segment byte-push-arg argnum)
1148                       (byte-generate-type-check segment type bind)
1149                       (incf pops)))
1150                    (t
1151                     (output-byte-with-operand segment byte-push-arg argnum)
1152                     (when type-check
1153                       (byte-generate-type-check segment type bind))
1154                     (output-set-lambda-var segment var env t)))))))
1155
1156       ;; Everything has been taken care of in the combination node.
1157       ((:let :mv-let :assignment))))
1158   (values))
1159
1160 ;;; This hashtable translates from n-ary function names to the
1161 ;;; two-arg-specific versions which we call to avoid &REST-arg consing.
1162 (defvar *two-arg-functions* (make-hash-table :test 'eq))
1163
1164 (dolist (fun '((sb!kernel:two-arg-ior  logior)
1165                (sb!kernel:two-arg-*  *)
1166                (sb!kernel:two-arg-+  +)
1167                (sb!kernel:two-arg-/  /)
1168                (sb!kernel:two-arg--  -)
1169                (sb!kernel:two-arg->  >)
1170                (sb!kernel:two-arg-<  <)
1171                (sb!kernel:two-arg-=  =)
1172                (sb!kernel:two-arg-lcm  lcm)
1173                (sb!kernel:two-arg-and  logand)
1174                (sb!kernel:two-arg-gcd  gcd)
1175                (sb!kernel:two-arg-xor  logxor)
1176
1177                (two-arg-char= char=)
1178                (two-arg-char< char<)
1179                (two-arg-char> char>)
1180                (two-arg-char-equal char-equal)
1181                (two-arg-char-lessp char-lessp)
1182                (two-arg-char-greaterp char-greaterp)
1183                (two-arg-string= string=)
1184                (two-arg-string< string<)
1185                (two-arg-string> string>)))
1186
1187   (setf (gethash (second fun) *two-arg-functions*) (first fun)))
1188
1189 ;;; If a system constant, push that, otherwise use a load-time constant.
1190 (defun output-push-fdefinition (segment name)
1191   (let ((offset (gethash `(%fdefinition-marker% . ,name)
1192                          *system-constant-codes*)))
1193     (if offset
1194         (output-byte-with-operand segment byte-push-system-constant
1195                                   offset)
1196         (output-push-load-time-constant segment :fdefinition name))))
1197
1198 (defun generate-byte-code-for-ref (segment ref cont)
1199   (declare (type sb!assem:segment segment) (type ref ref)
1200            (type continuation cont))
1201   (let ((info (continuation-info cont)))
1202     ;; If there is no info, then nobody wants the result.
1203     (when info
1204       (let ((values (byte-continuation-info-results info))
1205             (leaf (ref-leaf ref)))
1206         (cond
1207          ((eq values :fdefinition)
1208           (assert (and (global-var-p leaf)
1209                        (eq (global-var-kind leaf)
1210                            :global-function)))
1211           (let* ((name (global-var-name leaf))
1212                  (found (gethash name *two-arg-functions*)))
1213             (output-push-fdefinition
1214              segment
1215              (if (and found
1216                       (= (length (combination-args (continuation-dest cont)))
1217                          2))
1218                  found
1219                  name))))
1220          ((eql values 0)
1221           ;; really easy!
1222           nil)
1223          (t
1224           (etypecase leaf
1225             (constant
1226              (cond ((legal-immediate-constant-p leaf)
1227                      (output-push-constant-leaf segment leaf))
1228                    (t
1229                      (output-push-constant segment (leaf-name leaf))
1230                      (output-do-inline-function segment 'symbol-value))))
1231             (clambda
1232              (let* ((refered-env (lambda-environment leaf))
1233                     (closure (environment-closure refered-env)))
1234                (if (null closure)
1235                    (output-push-load-time-constant segment :entry leaf)
1236                    (let ((my-env (node-environment ref)))
1237                      (output-push-load-time-constant segment :entry leaf)
1238                      (dolist (thing closure)
1239                        (etypecase thing
1240                          (lambda-var
1241                           (output-ref-lambda-var segment thing my-env nil))
1242                          (nlx-info
1243                           (output-ref-nlx-info segment thing my-env))))
1244                      (output-push-int segment (length closure))
1245                      (output-do-xop segment 'make-closure)))))
1246             (functional
1247              (output-push-load-time-constant segment :entry leaf))
1248             (lambda-var
1249              (output-ref-lambda-var segment leaf (node-environment ref)))
1250             (global-var
1251              (ecase (global-var-kind leaf)
1252                ((:special :global :constant)
1253                 (output-push-constant segment (global-var-name leaf))
1254                 (output-do-inline-function segment 'symbol-value))
1255                (:global-function
1256                 (output-push-fdefinition segment (global-var-name leaf))
1257                 (output-do-xop segment 'fdefn-function-or-lose)))))
1258           (checked-canonicalize-values segment cont 1))))))
1259   (values))
1260
1261 (defun generate-byte-code-for-set (segment set cont)
1262   (declare (type sb!assem:segment segment) (type cset set)
1263            (type continuation cont))
1264   (let* ((leaf (set-var set))
1265          (info (continuation-info cont))
1266          (values (if info
1267                      (byte-continuation-info-results info)
1268                      0)))
1269     (unless (eql values 0)
1270       ;; Someone wants the value, so copy it.
1271       (output-do-xop segment 'dup))
1272     (etypecase leaf
1273       (global-var
1274        (ecase (global-var-kind leaf)
1275          ((:special :global)
1276           (output-push-constant segment (global-var-name leaf))
1277           (output-do-inline-function segment 'setf-symbol-value))))
1278       (lambda-var
1279        (output-set-lambda-var segment leaf (node-environment set))))
1280     (unless (eql values 0)
1281       (checked-canonicalize-values segment cont 1)))
1282   (values))
1283
1284 (defun generate-byte-code-for-local-call (segment call cont num-args)
1285   (let* ((lambda (combination-lambda call))
1286          (vars (lambda-vars lambda))
1287          (env (lambda-environment lambda)))
1288     (ecase (functional-kind lambda)
1289       ((:let :assignment)
1290        (dolist (var (reverse vars))
1291          (when (lambda-var-refs var)
1292            (output-set-lambda-var segment var env t))))
1293       (:mv-let
1294        (let ((do-check (member (continuation-type-check
1295                                 (first (basic-combination-args call)))
1296                                '(t :error))))
1297          (dolist (var (reverse vars))
1298            (when do-check
1299              (byte-generate-type-check segment (leaf-type var) call))
1300            (output-set-lambda-var segment var env t))))
1301       ((nil :optional :cleanup)
1302        ;; We got us a local call.
1303        (assert (not (eq num-args :unknown)))
1304        ;; Push any trailing placeholder args...
1305        (dolist (x (reverse (basic-combination-args call)))
1306          (when x (return))
1307          (output-push-int segment 0))
1308        ;; Then push closure vars.
1309        (let ((closure (environment-closure env)))
1310          (when closure
1311            (let ((my-env (node-environment call)))
1312              (dolist (thing (reverse closure))
1313                (etypecase thing
1314                  (lambda-var
1315                   (output-ref-lambda-var segment thing my-env nil))
1316                  (nlx-info
1317                   (output-ref-nlx-info segment thing my-env)))))
1318            (incf num-args (length closure))))
1319        (let ((results
1320               (let ((info (continuation-info cont)))
1321                 (if info
1322                     (byte-continuation-info-results info)
1323                     0))))
1324          ;; Emit the op for whatever flavor of call we are using.
1325          (let ((operand
1326                 (cond ((> num-args 6)
1327                        (output-push-int segment num-args)
1328                        7)
1329                       (t
1330                        num-args))))
1331            (multiple-value-bind (opcode ret-vals)
1332                (cond ((node-tail-p call)
1333                       (values byte-local-tail-call 0))
1334                      ((member results '(0 1))
1335                       (values byte-local-call 1))
1336                      (t
1337                       (values byte-local-multiple-call :unknown)))
1338              ;; ### :call-site
1339              (output-byte segment (logior opcode operand))
1340              ;; Emit a reference to the label.
1341              (output-reference segment
1342                                (byte-lambda-info-label (lambda-info lambda)))
1343              ;; ### :unknown-return
1344              ;; Fix up the results.
1345              (unless (node-tail-p call)
1346                (checked-canonicalize-values segment cont ret-vals))))))))
1347   (values))
1348
1349 (defun generate-byte-code-for-full-call (segment call cont num-args)
1350   (let ((info (basic-combination-info call))
1351         (results
1352          (let ((info (continuation-info cont)))
1353            (if info
1354                (byte-continuation-info-results info)
1355                0))))
1356     (cond
1357      (info
1358       ;; It's an inline function.
1359       (assert (not (node-tail-p call)))
1360       (let* ((type (inline-function-info-type info))
1361              (desired-args (function-type-nargs type))
1362              (supplied-results
1363               (nth-value 1
1364                          (values-types (function-type-returns type))))
1365              (leaf (ref-leaf (continuation-use (basic-combination-fun call)))))
1366         (cond ((slot-accessor-p leaf)
1367                (assert (= num-args (1- desired-args)))
1368                (output-push-int segment (dsd-index (slot-accessor-slot leaf))))
1369               (t
1370                (canonicalize-values segment desired-args num-args)))
1371         ;; ### :call-site
1372         (output-byte segment (logior byte-inline-function
1373                                      (inline-function-info-number info)))
1374         ;; ### :known-return
1375         (checked-canonicalize-values segment cont supplied-results)))
1376      (t
1377       (let ((operand
1378              (cond ((eq num-args :unknown)
1379                     7)
1380                    ((> num-args 6)
1381                     (output-push-int segment num-args)
1382                     7)
1383                    (t
1384                     num-args))))
1385         (when (eq (byte-continuation-info-results
1386                    (continuation-info
1387                     (basic-combination-fun call)))
1388                   :fdefinition)
1389           (setf operand (logior operand byte-named)))
1390         ;; ### :call-site
1391         (cond
1392          ((node-tail-p call)
1393           (output-byte segment (logior byte-tail-call operand)))
1394          (t
1395           (multiple-value-bind (opcode ret-vals)
1396               (case results
1397                 (:unknown (values byte-multiple-call :unknown))
1398                 ((0 1) (values byte-call 1))
1399                 (t (values byte-multiple-call :unknown)))
1400           (output-byte segment (logior opcode operand))
1401           ;; ### :unknown-return
1402           (checked-canonicalize-values segment cont ret-vals)))))))))
1403
1404 (defun generate-byte-code-for-known-call (segment call cont num-args)
1405   (block nil
1406     (catch 'give-up-ir1-transform
1407       (funcall (function-info-byte-compile (basic-combination-kind call)) call
1408                (let ((info (continuation-info cont)))
1409                  (if info
1410                      (byte-continuation-info-results info)
1411                      0))
1412                num-args segment)
1413       (return))
1414     (assert (member (byte-continuation-info-results
1415                      (continuation-info
1416                       (basic-combination-fun call)))
1417                     '(1 :fdefinition)))
1418     (generate-byte-code-for-full-call segment call cont num-args))
1419   (values))
1420
1421 (defun generate-byte-code-for-generic-combination (segment call cont)
1422   (declare (type sb!assem:segment segment) (type basic-combination call)
1423            (type continuation cont))
1424   (labels ((examine (args num-fixed)
1425              (cond
1426               ((null args)
1427                ;; None of the arugments supply :UNKNOWN values, so
1428                ;; we know exactly how many there are.
1429                num-fixed)
1430               (t
1431                (let* ((vals
1432                        (byte-continuation-info-results
1433                         (continuation-info (car args)))))
1434                  (cond
1435                   ((eq vals :unknown)
1436                    (unless (null (cdr args))
1437                      ;; There are (LENGTH ARGS) :UNKNOWN value blocks on
1438                      ;; the top of the stack. We need to combine them.
1439                      (output-push-int segment (length args))
1440                      (output-do-xop segment 'merge-unknown-values))
1441                    (unless (zerop num-fixed)
1442                      ;; There are num-fixed fixed args above the unknown
1443                      ;; values block that want in on the action also.
1444                      ;; So add num-fixed to the count.
1445                      (output-push-int segment num-fixed)
1446                      (output-do-inline-function segment '+))
1447                    :unknown)
1448                   (t
1449                    (examine (cdr args) (+ num-fixed vals)))))))))
1450     (let* ((args (basic-combination-args call))
1451            (kind (basic-combination-kind call))
1452            (num-args (if (and (eq kind :local)
1453                               (combination-p call))
1454                          (length args)
1455                          (examine args 0))))
1456       (case kind
1457         (:local
1458          (generate-byte-code-for-local-call segment call cont num-args))
1459         (:full
1460          (generate-byte-code-for-full-call segment call cont num-args))
1461         (t
1462          (generate-byte-code-for-known-call segment call cont num-args))))))
1463
1464 (defun generate-byte-code-for-basic-combination (segment call cont)
1465   (cond ((and (mv-combination-p call)
1466               (eq (continuation-function-name (basic-combination-fun call))
1467                   '%throw))
1468          ;; ### :internal-error
1469          (output-do-xop segment 'throw))
1470         (t
1471          (generate-byte-code-for-generic-combination segment call cont))))
1472
1473 (defun generate-byte-code-for-if (segment if cont)
1474   (declare (type sb!assem:segment segment) (type cif if)
1475            (ignore cont))
1476   (let* ((next-info (byte-block-info-next (block-info (node-block if))))
1477          (consequent-info (block-info (if-consequent if)))
1478          (alternate-info (block-info (if-alternative if))))
1479     (cond ((eq (byte-continuation-info-results
1480                 (continuation-info (if-test if)))
1481                :eq-test)
1482            (output-branch segment
1483                           byte-branch-if-eq
1484                           (byte-block-info-label consequent-info))
1485            (unless (eq next-info alternate-info)
1486              (output-branch segment
1487                             byte-branch-always
1488                             (byte-block-info-label alternate-info))))
1489           ((eq next-info consequent-info)
1490            (output-branch segment
1491                           byte-branch-if-false
1492                           (byte-block-info-label alternate-info)))
1493           (t
1494            (output-branch segment
1495                           byte-branch-if-true
1496                           (byte-block-info-label consequent-info))
1497            (unless (eq next-info alternate-info)
1498              (output-branch segment
1499                             byte-branch-always
1500                             (byte-block-info-label alternate-info)))))))
1501
1502 (defun generate-byte-code-for-return (segment return cont)
1503   (declare (type sb!assem:segment segment) (type creturn return)
1504            (ignore cont))
1505   (let* ((result (return-result return))
1506          (info (continuation-info result))
1507          (results (byte-continuation-info-results info)))
1508     (cond ((eq results :unknown)
1509            (setf results 7))
1510           ((> results 6)
1511            (output-byte-with-operand segment byte-push-int results)
1512            (setf results 7)))
1513     (output-byte segment (logior byte-return results)))
1514   (values))
1515
1516 (defun generate-byte-code-for-entry (segment entry cont)
1517   (declare (type sb!assem:segment segment) (type entry entry)
1518            (ignore cont))
1519   (dolist (exit (entry-exits entry))
1520     (let ((nlx-info (find-nlx-info entry (node-cont exit))))
1521       (when nlx-info
1522         (let ((kind (cleanup-kind (nlx-info-cleanup nlx-info))))
1523           (when (member kind '(:block :tagbody))
1524             ;; Generate a unique tag.
1525             (output-push-constant
1526              segment
1527              (format nil
1528                      "tag for ~A"
1529                      (component-name *component-being-compiled*)))
1530             (output-push-constant segment nil)
1531             (output-do-inline-function segment 'cons)
1532             ;; Save it so people can close over it.
1533             (output-do-xop segment 'dup)
1534             (output-byte-with-operand segment
1535                                       byte-pop-local
1536                                       (byte-nlx-info-stack-slot
1537                                        (nlx-info-info nlx-info)))
1538             ;; Now do the actual XOP.
1539             (ecase kind
1540               (:block
1541                (output-do-xop segment 'catch)
1542                (output-reference segment
1543                                  (byte-nlx-info-label
1544                                   (nlx-info-info nlx-info))))
1545               (:tagbody
1546                (output-do-xop segment 'tagbody)))
1547             (return))))))
1548   (values))
1549
1550 (defun generate-byte-code-for-exit (segment exit cont)
1551   (declare (ignore cont))
1552   (let ((nlx-info (find-nlx-info (exit-entry exit) (node-cont exit))))
1553     (output-byte-with-operand segment
1554                               byte-push-arg
1555                               (closure-position nlx-info
1556                                                 (node-environment exit)))
1557     (ecase (cleanup-kind (nlx-info-cleanup nlx-info))
1558       (:block
1559        ;; ### :internal-error
1560        (output-do-xop segment 'return-from))
1561       (:tagbody
1562        ;; ### :internal-error
1563        (output-do-xop segment 'go)
1564        (output-reference segment
1565                          (byte-nlx-info-label (nlx-info-info nlx-info)))))))
1566
1567 (defun generate-byte-code (segment component)
1568   (let ((*byte-component-info* (component-info component)))
1569     (do* ((info (byte-block-info-next (block-info (component-head component)))
1570                 next)
1571           (block (byte-block-info-block info) (byte-block-info-block info))
1572           (next (byte-block-info-next info) (byte-block-info-next info)))
1573          ((eq block (component-tail component)))
1574       (when (block-interesting block)
1575         (output-label segment (byte-block-info-label info))
1576         (do-nodes (node cont block)
1577           (etypecase node
1578             (bind (generate-byte-code-for-bind segment node cont))
1579             (ref (generate-byte-code-for-ref segment node cont))
1580             (cset (generate-byte-code-for-set segment node cont))
1581             (basic-combination
1582              (generate-byte-code-for-basic-combination
1583               segment node cont))
1584             (cif (generate-byte-code-for-if segment node cont))
1585             (creturn (generate-byte-code-for-return segment node cont))
1586             (entry (generate-byte-code-for-entry segment node cont))
1587             (exit
1588              (when (exit-entry node)
1589                (generate-byte-code-for-exit segment node cont)))))
1590         (let* ((succ (block-succ block))
1591                (first-succ (car succ))
1592                (last (block-last block)))
1593           (unless (or (cdr succ)
1594                       (eq (byte-block-info-block next) first-succ)
1595                       (eq (component-tail component) first-succ)
1596                       (and (basic-combination-p last)
1597                            (node-tail-p last)
1598                            ;; Tail local calls that have been
1599                            ;; converted to an assignment need the
1600                            ;; branch.
1601                            (not (and (eq (basic-combination-kind last) :local)
1602                                      (member (functional-kind
1603                                               (combination-lambda last))
1604                                              '(:let :assignment))))))
1605             (output-branch segment
1606                            byte-branch-always
1607                            (byte-block-info-label
1608                             (block-info first-succ))))))))
1609   (values))
1610 \f
1611 ;;;; special purpose annotate/compile optimizers
1612
1613 (defoptimizer (eq byte-annotate) ((this that) node)
1614   (declare (ignore this that))
1615   (when (if-p (continuation-dest (node-cont node)))
1616     (annotate-known-call node)
1617     t))
1618
1619 (defoptimizer (eq byte-compile) ((this that) call results num-args segment)
1620   (progn segment) ; ignorable.
1621   ;; We don't have to do anything, because everything is handled by
1622   ;; the IF byte-generator.
1623   (assert (eq results :eq-test))
1624   (assert (eql num-args 2))
1625   (values))
1626
1627 (defoptimizer (values byte-compile)
1628               ((&rest values) node results num-args segment)
1629   (canonicalize-values segment results num-args))
1630
1631 (defknown %byte-pop-stack (index) (values))
1632
1633 (defoptimizer (%byte-pop-stack byte-annotate) ((count) node)
1634   (assert (constant-continuation-p count))
1635   (annotate-continuation count 0)
1636   (annotate-continuation (basic-combination-fun node) 0)
1637   (setf (node-tail-p node) nil)
1638   t)
1639
1640 (defoptimizer (%byte-pop-stack byte-compile)
1641               ((count) node results num-args segment)
1642   (assert (and (zerop num-args) (zerop results)))
1643   (output-byte-with-operand segment byte-pop-n (continuation-value count)))
1644
1645 (defoptimizer (%special-bind byte-annotate) ((var value) node)
1646   (annotate-continuation var 0)
1647   (annotate-continuation value 1)
1648   (annotate-continuation (basic-combination-fun node) 0)
1649   (setf (node-tail-p node) nil)
1650   t)
1651
1652 (defoptimizer (%special-bind byte-compile)
1653               ((var value) node results num-args segment)
1654   (assert (and (eql num-args 1) (zerop results)))
1655   (output-push-constant segment (leaf-name (continuation-value var)))
1656   (output-do-inline-function segment '%byte-special-bind))
1657
1658 (defoptimizer (%special-unbind byte-annotate) ((var) node)
1659   (annotate-continuation var 0)
1660   (annotate-continuation (basic-combination-fun node) 0)
1661   (setf (node-tail-p node) nil)
1662   t)
1663
1664 (defoptimizer (%special-unbind byte-compile)
1665               ((var) node results num-args segment)
1666   (assert (and (zerop num-args) (zerop results)))
1667   (output-do-inline-function segment '%byte-special-unbind))
1668
1669 (defoptimizer (%catch byte-annotate) ((nlx-info tag) node)
1670   (annotate-continuation nlx-info 0)
1671   (annotate-continuation tag 1)
1672   (annotate-continuation (basic-combination-fun node) 0)
1673   (setf (node-tail-p node) nil)
1674   t)
1675
1676 (defoptimizer (%catch byte-compile)
1677               ((nlx-info tag) node results num-args segment)
1678   (progn node) ; ignore
1679   (assert (and (= num-args 1) (zerop results)))
1680   (output-do-xop segment 'catch)
1681   (let ((info (nlx-info-info (continuation-value nlx-info))))
1682     (output-reference segment (byte-nlx-info-label info))))
1683
1684 (defoptimizer (%cleanup-point byte-compile) (() node results num-args segment)
1685   (progn node segment) ; ignore
1686   (assert (and (zerop num-args) (zerop results))))
1687
1688 (defoptimizer (%catch-breakup byte-compile) (() node results num-args segment)
1689   (progn node) ; ignore
1690   (assert (and (zerop num-args) (zerop results)))
1691   (output-do-xop segment 'breakup))
1692
1693 (defoptimizer (%lexical-exit-breakup byte-annotate) ((nlx-info) node)
1694   (annotate-continuation nlx-info 0)
1695   (annotate-continuation (basic-combination-fun node) 0)
1696   (setf (node-tail-p node) nil)
1697   t)
1698
1699 (defoptimizer (%lexical-exit-breakup byte-compile)
1700               ((nlx-info) node results num-args segment)
1701   (assert (and (zerop num-args) (zerop results)))
1702   (let ((nlx-info (continuation-value nlx-info)))
1703     (when (ecase (cleanup-kind (nlx-info-cleanup nlx-info))
1704             (:block
1705              ;; We only want to do this for the fall-though case.
1706              (not (eq (car (block-pred (node-block node)))
1707                       (nlx-info-target nlx-info))))
1708             (:tagbody
1709              ;; Only want to do it once per tagbody.
1710              (not (byte-nlx-info-duplicate (nlx-info-info nlx-info)))))
1711       (output-do-xop segment 'breakup))))
1712
1713 (defoptimizer (%nlx-entry byte-annotate) ((nlx-info) node)
1714   (annotate-continuation nlx-info 0)
1715   (annotate-continuation (basic-combination-fun node) 0)
1716   (setf (node-tail-p node) nil)
1717   t)
1718
1719 (defoptimizer (%nlx-entry byte-compile)
1720               ((nlx-info) node results num-args segment)
1721   (progn node results) ; ignore
1722   (assert (eql num-args 0))
1723   (let* ((info (continuation-value nlx-info))
1724          (byte-info (nlx-info-info info)))
1725     (output-label segment (byte-nlx-info-label byte-info))
1726     ;; ### :non-local-entry
1727     (ecase (cleanup-kind (nlx-info-cleanup info))
1728       ((:catch :block)
1729        (checked-canonicalize-values segment
1730                                     (nlx-info-continuation info)
1731                                     :unknown))
1732       ((:tagbody :unwind-protect)))))
1733
1734 (defoptimizer (%unwind-protect byte-annotate)
1735               ((nlx-info cleanup-fun) node)
1736   (annotate-continuation nlx-info 0)
1737   (annotate-continuation cleanup-fun 0)
1738   (annotate-continuation (basic-combination-fun node) 0)
1739   (setf (node-tail-p node) nil)
1740   t)
1741
1742 (defoptimizer (%unwind-protect byte-compile)
1743               ((nlx-info cleanup-fun) node results num-args segment)
1744   (assert (and (zerop num-args) (zerop results)))
1745   (output-do-xop segment 'unwind-protect)
1746   (output-reference segment
1747                     (byte-nlx-info-label
1748                      (nlx-info-info
1749                       (continuation-value nlx-info)))))
1750
1751 (defoptimizer (%unwind-protect-breakup byte-compile)
1752               (() node results num-args segment)
1753   (progn node) ; ignore
1754   (assert (and (zerop num-args) (zerop results)))
1755   (output-do-xop segment 'breakup))
1756
1757 (defoptimizer (%continue-unwind byte-annotate) ((a b c) node)
1758   (annotate-continuation a 0)
1759   (annotate-continuation b 0)
1760   (annotate-continuation c 0)
1761   (annotate-continuation (basic-combination-fun node) 0)
1762   (setf (node-tail-p node) nil)
1763   t)
1764
1765 (defoptimizer (%continue-unwind byte-compile)
1766               ((a b c) node results num-args segment)
1767   (progn node) ; ignore
1768   (assert (member results '(0 nil)))
1769   (assert (eql num-args 0))
1770   (output-do-xop segment 'breakup))
1771
1772 (defoptimizer (%load-time-value byte-annotate) ((handle) node)
1773   (annotate-continuation handle 0)
1774   (annotate-continuation (basic-combination-fun node) 0)
1775   (setf (node-tail-p node) nil)
1776   t)
1777
1778 (defoptimizer (%load-time-value byte-compile)
1779               ((handle) node results num-args segment)
1780   (progn node) ; ignore
1781   (assert (zerop num-args))
1782   (output-push-load-time-constant segment :load-time-value
1783                                   (continuation-value handle))
1784   (canonicalize-values segment results 1))
1785 \f
1786 ;;; Make a byte-function for LAMBDA.
1787 (defun make-xep-for (lambda)
1788   (flet ((entry-point-for (entry)
1789            (let ((info (lambda-info entry)))
1790              (assert (byte-lambda-info-interesting info))
1791              (sb!assem:label-position (byte-lambda-info-label info)))))
1792     (let ((entry (lambda-entry-function lambda)))
1793       (etypecase entry
1794         (optional-dispatch
1795          (let ((rest-arg-p nil)
1796                (num-more 0))
1797            (declare (type index num-more))
1798            (collect ((keywords))
1799              (dolist (var (nthcdr (optional-dispatch-max-args entry)
1800                                   (optional-dispatch-arglist entry)))
1801                (let ((arg-info (lambda-var-arg-info var)))
1802                  (assert arg-info)
1803                  (ecase (arg-info-kind arg-info)
1804                    (:rest
1805                     (assert (not rest-arg-p))
1806                     (incf num-more)
1807                     (setf rest-arg-p t))
1808                    (:keyword
1809                     (let ((s-p (arg-info-supplied-p arg-info))
1810                           (default (arg-info-default arg-info)))
1811                       (incf num-more (if s-p 2 1))
1812                       (keywords (list (arg-info-keyword arg-info)
1813                                       (if (constantp default)
1814                                           (eval default)
1815                                           nil)
1816                                       (if s-p t nil))))))))
1817              (make-hairy-byte-function
1818               :name (leaf-name entry)
1819               :min-args (optional-dispatch-min-args entry)
1820               :max-args (optional-dispatch-max-args entry)
1821               :entry-points
1822               (mapcar #'entry-point-for (optional-dispatch-entry-points entry))
1823               :more-args-entry-point
1824               (entry-point-for (optional-dispatch-main-entry entry))
1825               :num-more-args num-more
1826               :rest-arg-p rest-arg-p
1827               :keywords-p
1828               (if (optional-dispatch-keyp entry)
1829                   (if (optional-dispatch-allowp entry)
1830                       :allow-others t))
1831               :keywords (keywords)))))
1832         (clambda
1833          (let ((args (length (lambda-vars entry))))
1834            (make-simple-byte-function
1835             :name (leaf-name entry)
1836             :num-args args
1837             :entry-point (entry-point-for entry))))))))
1838
1839 (defun generate-xeps (component)
1840   (let ((xeps nil))
1841     (dolist (lambda (component-lambdas component))
1842       (when (member (lambda-kind lambda) '(:external :top-level))
1843         (push (cons lambda (make-xep-for lambda)) xeps)))
1844     xeps))
1845 \f
1846 ;;;; noise to actually do the compile
1847
1848 (defun assign-locals (component)
1849   ;; Process all of the lambdas in component, and assign stack frame
1850   ;; locations for all the locals.
1851   (dolist (lambda (component-lambdas component))
1852     ;; We don't generate any code for :external lambdas, so we don't need
1853     ;; to allocate stack space. Also, we don't use the ``more'' entry,
1854     ;; so we don't need code for it.
1855     (cond
1856      ((or (eq (lambda-kind lambda) :external)
1857           (and (eq (lambda-kind lambda) :optional)
1858                (eq (optional-dispatch-more-entry
1859                     (lambda-optional-dispatch lambda))
1860                    lambda)))
1861       (setf (lambda-info lambda)
1862             (make-byte-lambda-info :interesting nil)))
1863      (t
1864       (let ((num-locals 0))
1865         (let* ((vars (lambda-vars lambda))
1866                (arg-num (+ (length vars)
1867                            (length (environment-closure
1868                                     (lambda-environment lambda))))))
1869           (dolist (var vars)
1870             (decf arg-num)
1871             (cond ((or (lambda-var-sets var) (lambda-var-indirect var))
1872                    (setf (leaf-info var)
1873                          (make-byte-lambda-var-info :offset num-locals))
1874                    (incf num-locals))
1875                   ((leaf-refs var)
1876                    (setf (leaf-info var)
1877                          (make-byte-lambda-var-info :argp t
1878                                                     :offset arg-num))))))
1879         (dolist (let (lambda-lets lambda))
1880           (dolist (var (lambda-vars let))
1881             (setf (leaf-info var)
1882                   (make-byte-lambda-var-info :offset num-locals))
1883             (incf num-locals)))
1884         (let ((entry-nodes-already-done nil))
1885           (dolist (nlx-info (environment-nlx-info (lambda-environment lambda)))
1886             (ecase (cleanup-kind (nlx-info-cleanup nlx-info))
1887               (:block
1888                (setf (nlx-info-info nlx-info)
1889                      (make-byte-nlx-info :stack-slot num-locals))
1890                (incf num-locals))
1891               (:tagbody
1892                (let* ((entry (cleanup-mess-up (nlx-info-cleanup nlx-info)))
1893                       (cruft (assoc entry entry-nodes-already-done)))
1894                  (cond (cruft
1895                         (setf (nlx-info-info nlx-info)
1896                               (make-byte-nlx-info :stack-slot (cdr cruft)
1897                                                   :duplicate t)))
1898                        (t
1899                         (push (cons entry num-locals) entry-nodes-already-done)
1900                         (setf (nlx-info-info nlx-info)
1901                               (make-byte-nlx-info :stack-slot num-locals))
1902                         (incf num-locals)))))
1903               ((:catch :unwind-protect)
1904                (setf (nlx-info-info nlx-info) (make-byte-nlx-info))))))
1905         (setf (lambda-info lambda)
1906               (make-byte-lambda-info :stack-size num-locals))))))
1907
1908   (values))
1909
1910 (defun byte-compile-component (component)
1911   (setf (component-info component) (make-byte-component-info))
1912   (maybe-mumble "ByteAnn ")
1913
1914   ;; Assign offsets for all the locals, and figure out which args can
1915   ;; stay in the argument area and which need to be moved into locals.
1916   (assign-locals component)
1917
1918   ;; Annotate every continuation with information about how we want the
1919   ;; values.
1920   (annotate-ir1 component)
1921
1922   ;; Determine what stack values are dead, and emit cleanup code to pop
1923   ;; them.
1924   (byte-stack-analyze component)
1925
1926   ;; Make sure any newly added blocks have a block-number.
1927   (dfo-as-needed component)
1928
1929   ;; Assign an ordering of the blocks.
1930   (control-analyze component #'make-byte-block-info)
1931
1932   ;; Find the start labels for the lambdas.
1933   (dolist (lambda (component-lambdas component))
1934     (let ((info (lambda-info lambda)))
1935       (when (byte-lambda-info-interesting info)
1936         (setf (byte-lambda-info-label info)
1937               (byte-block-info-label
1938                (block-info (node-block (lambda-bind lambda))))))))
1939
1940   ;; Delete any blocks that we are not going to emit from the emit order.
1941   (do-blocks (block component)
1942     (unless (block-interesting block)
1943       (let* ((info (block-info block))
1944              (prev (byte-block-info-prev info))
1945              (next (byte-block-info-next info)))
1946         (setf (byte-block-info-next prev) next)
1947         (setf (byte-block-info-prev next) prev))))
1948
1949   (maybe-mumble "ByteGen ")
1950   (let ((segment nil))
1951     (unwind-protect
1952         (progn
1953           (setf segment (sb!assem:make-segment :name "Byte Output"))
1954           (generate-byte-code segment component)
1955           (let ((code-length (sb!assem:finalize-segment segment))
1956                 (xeps (generate-xeps component))
1957                 (constants (byte-component-info-constants
1958                             (component-info component))))
1959             #!+sb-show
1960             (when *compiler-trace-output*
1961               (describe-component component *compiler-trace-output*)
1962               (describe-byte-component component xeps segment
1963                                        *compiler-trace-output*))
1964             (etypecase *compile-object*
1965               (fasl-file
1966                (maybe-mumble "FASL")
1967                (fasl-dump-byte-component segment code-length constants xeps
1968                                          *compile-object*))
1969               (core-object
1970                (maybe-mumble "Core")
1971                (make-core-byte-component segment code-length constants xeps
1972                                          *compile-object*))
1973               (null))))))
1974   (values))
1975 \f
1976 ;;;; extra stuff for debugging
1977
1978 #!+sb-show
1979 (defun dump-stack-info (component)
1980   (do-blocks (block component)
1981      (when (block-interesting block)
1982        (print-nodes block)
1983        (let ((info (block-info block)))
1984          (cond
1985           (info
1986            (format t
1987            "start-stack ~S~%consume ~S~%produce ~S~%end-stack ~S~%~
1988             total-consume ~S~%~@[nlx-entries ~S~%~]~@[nlx-entry-p ~S~%~]"
1989            (byte-block-info-start-stack info)
1990            (byte-block-info-consumes info)
1991            (byte-block-info-produces info)
1992            (byte-block-info-end-stack info)
1993            (byte-block-info-total-consumes info)
1994            (byte-block-info-nlx-entries info)
1995            (byte-block-info-nlx-entry-p info)))
1996           (t
1997            (format t "no info~%")))))))