Initial revision
[sbcl.git] / src / compiler / eval.lisp
1 ;;;; This file contains the IR1 interpreter. We first convert to the
2 ;;;; compiler's IR1, then interpret that.
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!EVAL")
14
15 (file-comment
16   "$Header$")
17 \f
18 ;;;; interpreter stack
19
20 (defvar *interpreted-function-cache-minimum-size* 25
21   #!+sb-doc
22   "If the interpreted function cache has more functions than this come GC time,
23   then attempt to prune it according to
24   *INTERPRETED-FUNCTION-CACHE-THRESHOLD*.")
25
26 (defvar *interpreted-function-cache-threshold* 3
27   #!+sb-doc
28   "If an interpreted function goes uncalled for more than this many GCs, then
29   it is eligible for flushing from the cache.")
30
31 (declaim (type (and fixnum unsigned-byte)
32                *interpreted-function-cache-minimum-size*
33                *interpreted-function-cache-threshold*))
34
35 ;;; The list of INTERPRETED-FUNCTIONS that have translated definitions.
36 (defvar *interpreted-function-cache* nil)
37 (declaim (type list *interpreted-function-cache*))
38
39 ;;; Setting this causes the stack operations to dump a trace.
40 ;;;
41 ;;; FIXME: perhaps should be #!+SB-SHOW
42 (defvar *eval-stack-trace* nil)
43
44 ;;; Push value on *eval-stack*, growing the stack if necessary. This returns
45 ;;; value. We save *eval-stack-top* in a local and increment the global before
46 ;;; storing value on the stack to prevent a GC timing problem. If we stored
47 ;;; value on the stack using *eval-stack-top* as an index, and we GC'ed before
48 ;;; incrementing *eval-stack-top*, then INTERPRETER-GC-HOOK would clear the
49 ;;; location.
50 (defun eval-stack-push (value)
51   (let ((len (length (the simple-vector *eval-stack*))))
52     (when (= len *eval-stack-top*)
53       (when *eval-stack-trace* (format t "[PUSH: growing stack.]~%"))
54       (let ((new-stack (make-array (ash len 1))))
55         (replace new-stack *eval-stack* :end1 len :end2 len)
56         (setf *eval-stack* new-stack))))
57   (let ((top *eval-stack-top*))
58     (when *eval-stack-trace* (format t "pushing ~D.~%" top))
59     (incf *eval-stack-top*)
60     (setf (svref *eval-stack* top) value)))
61
62 ;;; This returns the last value pushed on *eval-stack* and decrements the top
63 ;;; pointer. We forego setting elements off the end of the stack to nil for GC
64 ;;; purposes because there is a *before-gc-hook* to take care of this for us.
65 ;;; However, because of the GC hook, we must be careful to grab the value
66 ;;; before decrementing *eval-stack-top* since we could GC between the
67 ;;; decrement and the reference, and the hook would clear the stack slot.
68 (defun eval-stack-pop ()
69   (when (zerop *eval-stack-top*)
70     (error "attempt to pop empty eval stack"))
71   (let* ((new-top (1- *eval-stack-top*))
72          (value (svref *eval-stack* new-top)))
73     (when *eval-stack-trace* (format t "popping ~D --> ~S.~%" new-top value))
74     (setf *eval-stack-top* new-top)
75     value))
76
77 ;;; This allocates n locations on the stack, bumping the top pointer and
78 ;;; growing the stack if necessary. We set new slots to nil in case we GC
79 ;;; before having set them; we don't want to hold on to potential garbage
80 ;;; from old stack fluctuations.
81 (defun eval-stack-extend (n)
82   (let ((len (length (the simple-vector *eval-stack*))))
83     (when (> (+ n *eval-stack-top*) len)
84       (when *eval-stack-trace* (format t "[EXTEND: growing stack.]~%"))
85       (let ((new-stack (make-array (+ n (ash len 1)))))
86         (replace new-stack *eval-stack* :end1 len :end2 len)
87         (setf *eval-stack* new-stack))))
88   (let ((new-top (+ *eval-stack-top* n)))
89   (when *eval-stack-trace* (format t "extending to ~D.~%" new-top))
90     (do ((i *eval-stack-top* (1+ i)))
91         ((= i new-top))
92       (setf (svref *eval-stack* i) nil))
93     (setf *eval-stack-top* new-top)))
94
95 ;;; The anthesis of EVAL-STACK-EXTEND.
96 (defun eval-stack-shrink (n)
97   (when *eval-stack-trace*
98     (format t "shrinking to ~D.~%" (- *eval-stack-top* n)))
99   (decf *eval-stack-top* n))
100
101 ;;; This is used to shrink the stack back to a previous frame pointer.
102 (defun eval-stack-set-top (ptr)
103   (when *eval-stack-trace* (format t "setting top to ~D.~%" ptr))
104   (setf *eval-stack-top* ptr))
105
106 ;;; This returns a local variable from the current stack frame. This is used
107 ;;; for references the compiler represents as a lambda-var leaf. This is a
108 ;;; macro for SETF purposes.
109 ;;;
110 ;;; FIXME: used only in this file, needn't be in runtime
111 (defmacro eval-stack-local (fp offset)
112   `(svref *eval-stack* (+ ,fp ,offset)))
113 \f
114 ;;;; interpreted functions
115
116 ;;; The list of INTERPRETED-FUNCTIONS that have translated definitions.
117 (defvar *interpreted-function-cache* nil)
118 (declaim (type list *interpreted-function-cache*))
119
120 ;;; Return a function that will lazily convert Lambda when called, and will
121 ;;; cache translations.
122 (defun make-interpreted-function (lambda)
123   (let ((res (%make-interpreted-function :lambda lambda
124                                          :arglist (second lambda))))
125     (setf (funcallable-instance-function res)
126           #'(instance-lambda (&rest args)
127                (let ((fun (interpreted-function-definition res))
128                      (args (cons (length args) args)))
129                  (setf (interpreted-function-gcs res) 0)
130                  (internal-apply (or fun (convert-interpreted-fun res))
131                                  args '#()))))
132     res))
133
134 ;;; Eval a FUNCTION form, grab the definition and stick it in.
135 (defun convert-interpreted-fun (fun)
136   (declare (type interpreted-function fun))
137   (let* ((new (interpreted-function-definition
138                (internal-eval `#',(interpreted-function-lambda fun)
139                               (interpreted-function-converted-once fun)))))
140     (setf (interpreted-function-definition fun) new)
141     (setf (interpreted-function-converted-once fun) t)
142     (let ((name (interpreted-function-%name fun)))
143       (setf (sb!c::leaf-name new) name)
144       (setf (sb!c::leaf-name (sb!c::main-entry
145                               (sb!c::functional-entry-function new)))
146             name))
147     (push fun *interpreted-function-cache*)
148     new))
149
150 ;;; Get the CLAMBDA for the XEP, then look at the inline expansion info in
151 ;;; the real function.
152 (defun interpreted-function-lambda-expression (x)
153   (let ((lambda (interpreted-function-lambda x)))
154     (if lambda
155         (values lambda nil (interpreted-function-%name x))
156         (let ((fun (sb!c::functional-entry-function
157                     (interpreted-function-definition x))))
158           (values (sb!c::functional-inline-expansion fun)
159                   (if (let ((env (sb!c::functional-lexenv fun)))
160                         (or (sb!c::lexenv-functions env)
161                             (sb!c::lexenv-variables env)
162                             (sb!c::lexenv-blocks env)
163                             (sb!c::lexenv-tags env)))
164                       t nil)
165                   (or (interpreted-function-%name x)
166                       (sb!c::component-name
167                        (sb!c::block-component
168                         (sb!c::node-block
169                          (sb!c::lambda-bind (sb!c::main-entry fun)))))))))))
170
171 ;;; Return a FUNCTION-TYPE describing an eval function. We just grab the
172 ;;; LEAF-TYPE of the definition, converting the definition if not currently
173 ;;; cached.
174 (defvar *already-looking-for-type-of* nil)
175 (defun interpreted-function-type (fun)
176   (if (member fun *already-looking-for-type-of*)
177       (specifier-type 'function)
178       (let* ((*already-looking-for-type-of*
179               (cons fun *already-looking-for-type-of*))
180              (def (or (interpreted-function-definition fun)
181                       (sb!sys:without-gcing
182                        (convert-interpreted-fun fun)
183                        (interpreted-function-definition fun)))))
184         (sb!c::leaf-type (sb!c::functional-entry-function def)))))
185
186 (defun interpreted-function-name (x)
187   (multiple-value-bind (ig1 ig2 res) (interpreted-function-lambda-expression x)
188     (declare (ignore ig1 ig2))
189     res))
190 (defun (setf interpreted-function-name) (val x)
191   (let ((def (interpreted-function-definition x)))
192     (when def
193       (setf (sb!c::leaf-name def) val)
194       (setf (sb!c::leaf-name (sb!c::main-entry (sb!c::functional-entry-function
195                                                 def)))
196             val))
197     (setf (interpreted-function-%name x) val)))
198
199 (defun interpreter-gc-hook ()
200   ;; Clear the unused portion of the eval stack.
201   (let ((len (length (the simple-vector *eval-stack*))))
202     (do ((i *eval-stack-top* (1+ i)))
203         ((= i len))
204       (setf (svref *eval-stack* i) nil)))
205
206   ;; KLUDGE: I'd like to get rid of this, since it adds complexity and causes
207   ;; confusion. (It's not just academic that it causes confusion. When working
208   ;; on the original cross-compiler, I ran across what looked
209   ;; as though it might be a subtle writing-to-the-host-SBCL-compiler-data bug
210   ;; in my cross-compiler code, which turned out to be just a case of compiler
211   ;; warnings coming from recompilation of a flushed-from-the-cache interpreted
212   ;; function. Since it took me a long while to realize how many things the
213   ;; problem depended on (since it was tied up with magic numbers of GC cycles,
214   ;; egads!) I blew over a day trying to isolate the problem in a small test
215   ;; case.
216   ;;
217   ;; The cache-flushing seems to be motivated by efficiency concerns, which
218   ;; seem misplaced when the user chooses to use the interpreter. However, it
219   ;; also interacts with SAVE, and I veered off from deleting it wholesale when
220   ;; I noticed that. After the whole system is working, though, I'd like to
221   ;; revisit this decision. -- WHN 19990713
222   (let ((num (- (length *interpreted-function-cache*)
223                 *interpreted-function-cache-minimum-size*)))
224     (when (plusp num)
225       (setq *interpreted-function-cache*
226             (delete-if #'(lambda (x)
227                            (when (>= (interpreted-function-gcs x)
228                                      *interpreted-function-cache-threshold*)
229                              (setf (interpreted-function-definition x) nil)
230                              t))
231                        *interpreted-function-cache*
232                        :count num))))
233   (dolist (fun *interpreted-function-cache*)
234     (incf (interpreted-function-gcs fun))))
235 (pushnew 'interpreter-gc-hook sb!ext:*before-gc-hooks*)
236
237 (defun flush-interpreted-function-cache ()
238   #!+sb-doc
239   "Clear all entries in the eval function cache. This allows the internal
240   representation of the functions to be reclaimed, and also lazily forces
241   macroexpansions to be recomputed."
242   (dolist (fun *interpreted-function-cache*)
243     (setf (interpreted-function-definition fun) nil))
244   (setq *interpreted-function-cache* ()))
245 \f
246 ;;;; INTERNAL-APPLY-LOOP macros
247
248 ;;;; These macros are intimately related to INTERNAL-APPLY-LOOP. They assume
249 ;;;; variables established by this function, and they assume they can return
250 ;;;; from a block by that name. This is sleazy, but we justify it as follows:
251 ;;;; They are so specialized in use, and their invocation became lengthy, that
252 ;;;; we allowed them to slime some access to things in their expanding
253 ;;;; environment. These macros don't really extend our Lisp syntax, but they do
254 ;;;; provide some template expansion service; it is these cleaner circumstance
255 ;;;; that require a more rigid programming style.
256 ;;;;
257 ;;;; Since these are macros expanded almost solely for COMBINATION nodes,
258 ;;;; they cascade from the end of this logical page to the beginning here.
259 ;;;; Therefore, it is best you start looking at them from the end of this
260 ;;;; section, backwards from normal scanning mode for Lisp code.
261
262 ;;; This runs a function on some arguments from the stack. If the combination
263 ;;; occurs in a tail recursive position, then we do the call such that we
264 ;;; return from tail-p-function with whatever values the call produces. With a
265 ;;; :local call, we have to restore the stack to its previous frame before
266 ;;; doing the call. The :full call mechanism does this for us. If it is NOT a
267 ;;; tail recursive call, and we're in a multiple value context, then then push
268 ;;; a list of the returned values. Do the same thing if we're in a :return
269 ;;; context. Push a single value, without listifying it, for a :single value
270 ;;; context. Otherwise, just call for side effect.
271 ;;;
272 ;;; Node is the combination node, and cont is its continuation. Frame-ptr
273 ;;; is the current frame pointer, and closure is the current environment for
274 ;;; closure variables. Call-type is either :full or :local, and when it is
275 ;;; local, lambda is the IR1 lambda to apply.
276 ;;;
277 ;;; This assumes the following variables are present: node, cont, frame-ptr,
278 ;;; and closure. It also assumes a block named internal-apply-loop.
279 ;;;
280 ;;; FIXME: used only in this file, needn't be in runtime
281 ;;; FIXME: down with DO-FOO names for non-iteration constructs!
282 (defmacro do-combination (call-type lambda mv-or-normal)
283   (let* ((args (gensym))
284          (calling-closure (gensym))
285          (invoke-fun (ecase mv-or-normal
286                        (:mv-call 'mv-internal-invoke)
287                        (:normal 'internal-invoke)))
288          (args-form (ecase mv-or-normal
289                       (:mv-call
290                        `(mv-eval-stack-args
291                          (length (sb!c::mv-combination-args node))))
292                       (:normal
293                        `(eval-stack-args (sb!c:lambda-eval-info-args-passed
294                                           (sb!c::lambda-info ,lambda))))))
295          (call-form (ecase call-type
296                       (:full `(,invoke-fun
297                                (length (sb!c::basic-combination-args node))))
298                       (:local `(internal-apply
299                                 ,lambda ,args-form
300                                 (compute-closure node ,lambda frame-ptr
301                                                  closure)
302                                 nil))))
303          (tailp-call-form
304           (ecase call-type
305             (:full `(return-from
306                      internal-apply-loop
307                      ;; INVOKE-FUN takes care of the stack itself.
308                      (,invoke-fun (length (sb!c::basic-combination-args node))
309                                   frame-ptr)))
310             (:local `(let ((,args ,args-form)
311                            (,calling-closure
312                             (compute-closure node ,lambda frame-ptr closure)))
313                        ;; No need to clean up stack slots for GC due to
314                        ;; SB!EXT:*BEFORE-GC-HOOK*.
315                        (eval-stack-set-top frame-ptr)
316                        (return-from
317                         internal-apply-loop
318                         (internal-apply ,lambda ,args ,calling-closure
319                                         nil)))))))
320     `(cond ((sb!c::node-tail-p node)
321             ,tailp-call-form)
322            (t
323             (ecase (sb!c::continuation-info cont)
324               ((:multiple :return)
325                (eval-stack-push (multiple-value-list ,call-form)))
326               (:single
327                (eval-stack-push ,call-form))
328               (:unused ,call-form))))))
329
330 ;;; This sets the variable block in INTERNAL-APPLY-LOOP, and it announces this
331 ;;; by setting set-block-p for later loop iteration maintenance.
332 ;;;
333 ;;; FIXME: used only in this file, needn't be in runtime
334 (defmacro set-block (exp)
335   `(progn
336      (setf block ,exp)
337      (setf set-block-p t)))
338
339 ;;; This sets all the iteration variables in INTERNAL-APPLY-LOOP to iterate
340 ;;; over a new block's nodes. Block-exp is optional because sometimes we have
341 ;;; already set block, and we only need to bring the others into agreement.
342 ;;; If we already set block, then clear the variable that announces this,
343 ;;; set-block-p.
344 ;;;
345 ;;; FIXME: used only in this file, needn't be in runtime
346 (defmacro change-blocks (&optional block-exp)
347   `(progn
348      ,(if block-exp
349           `(setf block ,block-exp)
350           `(setf set-block-p nil))
351      (setf node (sb!c::continuation-next (sb!c::block-start block)))
352      (setf last-cont (sb!c::node-cont (sb!c::block-last block)))))
353
354 ;;; This controls printing visited nodes in INTERNAL-APPLY-LOOP. We use it
355 ;;; here, and INTERNAL-INVOKE uses it to print function call looking output
356 ;;; to further describe sb!c::combination nodes.
357 (defvar *internal-apply-node-trace* nil)
358 (defun maybe-trace-funny-fun (node name &rest args)
359   (when *internal-apply-node-trace*
360     (format t "(~S ~{ ~S~})  c~S~%"
361             name args (sb!c::cont-num (sb!c::node-cont node)))))
362
363 ;;; This implements the intention of the virtual function name. This is a
364 ;;; macro because some of these actions must occur without a function call.
365 ;;; For example, calling a dispatch function to implement special binding would
366 ;;; be a no-op because returning from that function would cause the system to
367 ;;; undo any special bindings it established.
368 ;;;
369 ;;; NOTE: update SB!C:ANNOTATE-COMPONENT-FOR-EVAL and/or
370 ;;; sb!c::undefined-funny-funs if you add or remove branches in this routine.
371 ;;;
372 ;;; This assumes the following variables are present: node, cont, frame-ptr,
373 ;;; args, closure, block, and last-cont. It also assumes a block named
374 ;;; internal-apply-loop.
375 ;;;
376 ;;; FIXME: used only in this file, needn't be in runtime
377 ;;; FIXME: down with DO-FOO names for non-iteration constructs!
378 (defmacro do-funny-function (funny-fun-name)
379   (let ((name (gensym)))
380     `(let ((,name ,funny-fun-name))
381        (ecase ,name
382          (sb!c::%special-bind
383           (let ((value (eval-stack-pop))
384                 (global-var (eval-stack-pop)))
385             (maybe-trace-funny-fun node ,name global-var value)
386             (sb!sys:%primitive sb!c:bind
387                                value
388                                (sb!c::global-var-name global-var))))
389          (sb!c::%special-unbind
390           ;; Throw away arg telling me which special, and tell the dynamic
391           ;; binding mechanism to unbind one variable.
392           (eval-stack-pop)
393           (maybe-trace-funny-fun node ,name)
394           (sb!sys:%primitive sb!c:unbind))
395          (sb!c::%catch
396           (let* ((tag (eval-stack-pop))
397                  (nlx-info (eval-stack-pop))
398                  (fell-through-p nil)
399                  ;; Ultimately THROW and CATCH will fix the interpreter's stack
400                  ;; since this is necessary for compiled CATCH's and those in
401                  ;; the initial top level function.
402                  (stack-top *eval-stack-top*)
403                  (values
404                   (multiple-value-list
405                    (catch tag
406                      (maybe-trace-funny-fun node ,name tag)
407                      (multiple-value-setq (block node cont last-cont)
408                        (internal-apply-loop (sb!c::continuation-next cont)
409                                             frame-ptr lambda args closure))
410                      (setf fell-through-p t)))))
411             (cond (fell-through-p
412                    ;; We got here because we just saw the SB!C::%CATCH-BREAKUP
413                    ;; funny function inside the above recursive call to
414                    ;; INTERNAL-APPLY-LOOP. Therefore, we just received and
415                    ;; stored the current state of evaluation for falling
416                    ;; through.
417                    )
418                   (t
419                    ;; Fix up the interpreter's stack after having thrown here.
420                    ;; We won't need to do this in the final implementation.
421                    (eval-stack-set-top stack-top)
422                    ;; Take the values received in the list bound above, and
423                    ;; massage them into the form expected by the continuation
424                    ;; of the non-local-exit info.
425                    (ecase (sb!c::continuation-info
426                            (sb!c::nlx-info-continuation nlx-info))
427                      (:single
428                       (eval-stack-push (car values)))
429                      ((:multiple :return)
430                       (eval-stack-push values))
431                      (:unused))
432                    ;; We want to continue with the code after the CATCH body.
433                    ;; The non-local-exit info tells us where this is, but we
434                    ;; know that block only contains a call to the funny
435                    ;; function SB!C::%NLX-ENTRY, which simply is a place holder
436                    ;; for the compiler IR1. We want to skip the target block
437                    ;; entirely, so we say it is the block we're in now and say
438                    ;; the current cont is the last-cont. This makes the COND
439                    ;; at the end of INTERNAL-APPLY-LOOP do the right thing.
440                    (setf block (sb!c::nlx-info-target nlx-info))
441                    (setf cont last-cont)))))
442          (sb!c::%unwind-protect
443           ;; Cleanup function not pushed due to special-case :UNUSED
444           ;; annotation in ANNOTATE-COMPONENT-FOR-EVAL.
445           (let* ((nlx-info (eval-stack-pop))
446                  (fell-through-p nil)
447                  (stack-top *eval-stack-top*))
448             (unwind-protect
449                 (progn
450                   (maybe-trace-funny-fun node ,name)
451                   (multiple-value-setq (block node cont last-cont)
452                     (internal-apply-loop (sb!c::continuation-next cont)
453                                          frame-ptr lambda args closure))
454                   (setf fell-through-p t))
455               (cond (fell-through-p
456                      ;; We got here because we just saw the
457                      ;; SB!C::%UNWIND-PROTECT-BREAKUP funny function inside the
458                      ;; above recursive call to INTERNAL-APPLY-LOOP.
459                      ;; Therefore, we just received and stored the current
460                      ;; state of evaluation for falling through.
461                      )
462                     (t
463                      ;; Fix up the interpreter's stack after having thrown
464                      ;; here. We won't need to do this in the final
465                      ;; implementation.
466                      (eval-stack-set-top stack-top)
467                      ;; Push some bogus values for exit context to keep the
468                      ;; MV-BIND in the UNWIND-PROTECT translation happy.
469                      (eval-stack-push '(nil nil 0))
470                      (let ((node (sb!c::continuation-next
471                                   (sb!c::block-start
472                                    (car (sb!c::block-succ
473                                          (sb!c::nlx-info-target nlx-info)))))))
474                        (internal-apply-loop node frame-ptr lambda args
475                                             closure)))))))
476          ((sb!c::%catch-breakup
477            sb!c::%unwind-protect-breakup
478            sb!c::%continue-unwind)
479           ;; This shows up when we locally exit a CATCH body -- fell through.
480           ;; Return the current state of evaluation to the previous invocation
481           ;; of INTERNAL-APPLY-LOOP which happens to be running in the
482           ;; SB!C::%CATCH branch of this code.
483           (maybe-trace-funny-fun node ,name)
484           (return-from internal-apply-loop
485                        (values block node cont last-cont)))
486          (sb!c::%nlx-entry
487           (maybe-trace-funny-fun node ,name)
488           ;; This just marks a spot in the code for CATCH, UNWIND-PROTECT, and
489           ;; non-local lexical exits (GO or RETURN-FROM).
490           ;; Do nothing since sb!c::%catch does it all when it catches a THROW.
491           ;; Do nothing since sb!c::%unwind-protect does it all when
492           ;; it catches a THROW.
493           )
494          (sb!c::%more-arg-context
495           (let* ((fixed-arg-count (1+ (eval-stack-pop)))
496                  ;; Add 1 to actual fixed count for extra arg expected by
497                  ;; external entry points (XEP) which some IR1 lambdas have.
498                  ;; The extra arg is the number of arguments for arg count
499                  ;; consistency checking. SB!C::%MORE-ARG-CONTEXT always runs
500                  ;; within an XEP, so the lambda has an extra arg.
501                  (more-args (nthcdr fixed-arg-count args)))
502             (maybe-trace-funny-fun node ,name fixed-arg-count)
503             (assert (eq (sb!c::continuation-info cont) :multiple))
504             (eval-stack-push (list more-args (length more-args)))))
505          (sb!c::%unknown-values
506           (error "SB!C::%UNKNOWN-VALUES should never be in interpreter's IR1."))
507          (sb!c::%lexical-exit-breakup
508           ;; We see this whenever we locally exit the extent of a lexical
509           ;; target. That is, we are truly locally exiting an extent we could
510           ;; have non-locally lexically exited. Return the :fell-through flag
511           ;; and the current state of evaluation to the previous invocation
512           ;; of INTERNAL-APPLY-LOOP which happens to be running in the
513           ;; sb!c::entry branch of INTERNAL-APPLY-LOOP.
514           (maybe-trace-funny-fun node ,name)
515           ;; Discard the NLX-INFO arg...
516           (eval-stack-pop)
517           (return-from internal-apply-loop
518                        (values :fell-through block node cont last-cont)))))))
519
520 ;;; This expands for the two types of combination nodes INTERNAL-APPLY-LOOP
521 ;;; sees. Type is either :mv-call or :normal. Node is the combination node,
522 ;;; and cont is its continuation. Frame-ptr is the current frame pointer, and
523 ;;; closure is the current environment for closure variables.
524 ;;;
525 ;;; Most of the real work is done by DO-COMBINATION. This first determines if
526 ;;; the combination node describes a :full call which DO-COMBINATION directly
527 ;;; handles. If the call is :local, then we either invoke an IR1 lambda, or we
528 ;;; just bind some LET variables. If the call is :local, and type is :mv-call,
529 ;;; then we can only be binding multiple values. Otherwise, the combination
530 ;;; node describes a function known to the compiler, but this may be a funny
531 ;;; function that actually isn't ever defined. We either take some action for
532 ;;; the funny function or do a :full call on the known true function, but the
533 ;;; interpreter doesn't do optimizing stuff for functions known to the
534 ;;; compiler.
535 ;;;
536 ;;; This assumes the following variables are present: node, cont, frame-ptr,
537 ;;; and closure. It also assumes a block named internal-apply-loop.
538 ;;;
539 ;;; FIXME: used only in this file, needn't be in runtime
540 (defmacro combination-node (type)
541   (let* ((kind (gensym))
542          (fun (gensym))
543          (lambda (gensym))
544          (letp (gensym))
545          (letp-bind (ecase type
546                       (:mv-call nil)
547                       (:normal
548                        `((,letp (eq (sb!c::functional-kind ,lambda) :let))))))
549          (local-branch
550           (ecase type
551             (:mv-call
552              `(store-mv-let-vars ,lambda frame-ptr
553                                  (length (sb!c::mv-combination-args node))))
554             (:normal
555              `(if ,letp
556                   (store-let-vars ,lambda frame-ptr)
557                   (do-combination :local ,lambda ,type))))))
558     `(let ((,kind (sb!c::basic-combination-kind node))
559            (,fun (sb!c::basic-combination-fun node)))
560        (cond ((member ,kind '(:full :error))
561               (do-combination :full nil ,type))
562              ((eq ,kind :local)
563               (let* ((,lambda (sb!c::ref-leaf (sb!c::continuation-use ,fun)))
564                      ,@letp-bind)
565                 ,local-branch))
566              ((eq (sb!c::continuation-info ,fun) :unused)
567               (assert (typep ,kind 'sb!c::function-info))
568               (do-funny-function (sb!c::continuation-function-name ,fun)))
569              (t
570               (assert (typep ,kind 'sb!c::function-info))
571               (do-combination :full nil ,type))))))
572
573 (defun trace-eval (on)
574   (setf *eval-stack-trace* on)
575   (setf *internal-apply-node-trace* on))
576 \f
577 ;;;; INTERNAL-EVAL
578
579 ;;; Evaluate an arbitary form. We convert the form, then call internal
580 ;;; apply on it. If *ALREADY-EVALED-THIS* is true, then we bind it to NIL
581 ;;; around the apply to limit the inhibition to the lexical scope of the
582 ;;; EVAL-WHEN.
583 (defun internal-eval (form &optional quietly)
584   (let ((res (sb!c:compile-for-eval form quietly)))
585     (if *already-evaled-this*
586         (let ((*already-evaled-this* nil))
587           (internal-apply res nil '#()))
588         (internal-apply res nil '#()))))
589
590 ;;; Later this will probably be the same weird internal thing the compiler
591 ;;; makes to represent these things.
592 (defun make-indirect-value-cell (value)
593   (list value))
594 ;;; FIXME: used only in this file, needn't be in runtime
595 (defmacro indirect-value (value-cell)
596   `(car ,value-cell))
597
598 ;;; This passes on a node's value appropriately, possibly returning from
599 ;;; function to do so. When we are tail-p, don't push the value, return it on
600 ;;; the system's actual call stack; when we blow out of function this way, we
601 ;;; must return the interpreter's stack to the its state before this call to
602 ;;; function. When we're in a multiple value context or heading for a return
603 ;;; node, we push a list of the value for easier handling later. Otherwise,
604 ;;; just push the value on the interpreter's stack.
605 ;;;
606 ;;; FIXME: maybe used only in this file, if so, needn't be in runtime
607 (defmacro value (node info value frame-ptr function)
608   `(cond ((sb!c::node-tail-p ,node)
609           (eval-stack-set-top ,frame-ptr)
610           (return-from ,function ,value))
611          ((member ,info '(:multiple :return) :test #'eq)
612           (eval-stack-push (list ,value)))
613          (t (assert (eq ,info :single))
614             (eval-stack-push ,value))))
615
616 (defun maybe-trace-nodes (node)
617   (when *internal-apply-node-trace*
618     (format t "<~A-node> c~S~%"
619             (type-of node)
620             (sb!c::cont-num (sb!c::node-cont node)))))
621
622 ;;; This interprets lambda, a compiler IR1 data structure representing a
623 ;;; function, applying it to args. Closure is the environment in which to run
624 ;;; lambda, the variables and such closed over to form lambda. The call occurs
625 ;;; on the interpreter's stack, so save the current top and extend the stack
626 ;;; for this lambda's call frame. Then store the args into locals on the
627 ;;; stack.
628 ;;;
629 ;;; Args is the list of arguments to apply to. If IGNORE-UNUSED is true, then
630 ;;; values for un-read variables are present in the argument list, and must be
631 ;;; discarded (always true except in a local call.)  Args may run out of values
632 ;;; before vars runs out of variables (in the case of an XEP with optionals);
633 ;;; we just do CAR of nil and store nil. This is not the proper defaulting
634 ;;; (which is done by explicit code in the XEP.)
635 (defun internal-apply (lambda args closure &optional (ignore-unused t))
636   (let ((frame-ptr *eval-stack-top*))
637     (eval-stack-extend (sb!c:lambda-eval-info-frame-size (sb!c::lambda-info lambda)))
638     (do ((vars (sb!c::lambda-vars lambda) (cdr vars))
639          (args args))
640         ((null vars))
641       (let ((var (car vars)))
642         (cond ((sb!c::leaf-refs var)
643                (setf (eval-stack-local frame-ptr (sb!c::lambda-var-info var))
644                      (if (sb!c::lambda-var-indirect var)
645                          (make-indirect-value-cell (pop args))
646                          (pop args))))
647               (ignore-unused (pop args)))))
648     (internal-apply-loop (sb!c::lambda-bind lambda) frame-ptr lambda args
649                          closure)))
650
651 ;;; This does the work of INTERNAL-APPLY. This also calls itself
652 ;;; recursively for certain language features, such as CATCH. First is
653 ;;; the node at which to start interpreting. FRAME-PTR is the current
654 ;;; frame pointer for accessing local variables. LAMBDA is the IR1
655 ;;; lambda from which comes the nodes a given call to this function
656 ;;; processes, and CLOSURE is the environment for interpreting LAMBDA.
657 ;;; ARGS is the argument list for the lambda given to INTERNAL-APPLY,
658 ;;; and we have to carry it around with us in case of &more-arg or
659 ;;; &rest-arg processing which is represented explicitly in the
660 ;;; compiler's IR1.
661 ;;;
662 ;;; KLUDGE: Due to having a truly tail recursive interpreter, some of
663 ;;; the branches handling a given node need to RETURN-FROM this
664 ;;; routine. Also, some calls this makes to do work for it must occur
665 ;;; in tail recursive positions. Because of this required access to
666 ;;; this function lexical environment and calling positions, we often
667 ;;; are unable to break off logical chunks of code into functions. We
668 ;;; have written macros intended solely for use in this routine, and
669 ;;; due to all the local stuff they need to access and length complex
670 ;;; calls, we have written them to sleazily access locals from this
671 ;;; routine. In addition to assuming a block named internal-apply-loop
672 ;;; exists, they set and reference the following variables: NODE,
673 ;;; CONT, FRAME-PTR, CLOSURE, BLOCK, LAST-CONT, and SET-BLOCK-P.
674 ;;; FIXME: Perhaps this kludge could go away if we convert to a
675 ;;; compiler-only implementation?
676 (defun internal-apply-loop (first frame-ptr lambda args closure)
677   ;; FIXME: This will cause source code location information to be compiled
678   ;; into the executable, which will probably cause problems for users running
679   ;; without the sources and/or without the build-the-system readtable.
680   (declare (optimize (debug 2)))
681   (let* ((block (sb!c::node-block first))
682          (last-cont (sb!c::node-cont (sb!c::block-last block)))
683          (node first)
684          (set-block-p nil))
685       (loop
686         (let ((cont (sb!c::node-cont node)))
687           (etypecase node
688             (sb!c::ref
689              (maybe-trace-nodes node)
690              (let ((info (sb!c::continuation-info cont)))
691                (unless (eq info :unused)
692                  (value node info (leaf-value node frame-ptr closure)
693                         frame-ptr internal-apply-loop))))
694             (sb!c::combination
695              (maybe-trace-nodes node)
696              (combination-node :normal))
697             (sb!c::cif
698              (maybe-trace-nodes node)
699              ;; IF nodes always occur at the end of a block, so pick another.
700              (set-block (if (eval-stack-pop)
701                             (sb!c::if-consequent node)
702                             (sb!c::if-alternative node))))
703             (sb!c::bind
704              (maybe-trace-nodes node)
705              ;; Ignore bind nodes since INTERNAL-APPLY extends the stack for
706              ;; all of a lambda's locals, and the sb!c::combination branch
707              ;; handles LET binds (moving values off stack top into locals).
708              )
709             (sb!c::cset
710              (maybe-trace-nodes node)
711              (let ((info (sb!c::continuation-info cont))
712                    (res (set-leaf-value node frame-ptr closure
713                                         (eval-stack-pop))))
714                (unless (eq info :unused)
715                  (value node info res frame-ptr internal-apply-loop))))
716             (sb!c::entry
717              (maybe-trace-nodes node)
718              (let ((info (cdr (assoc node (sb!c:lambda-eval-info-entries
719                                            (sb!c::lambda-info lambda))))))
720                ;; No info means no-op entry for CATCH or UNWIND-PROTECT.
721                (when info
722                  ;; Store stack top for restoration in local exit situation
723                  ;; in sb!c::exit branch.
724                  (setf (eval-stack-local frame-ptr
725                                          (sb!c:entry-node-info-st-top info))
726                        *eval-stack-top*)
727                  (let ((tag (sb!c:entry-node-info-nlx-tag info)))
728                    (when tag
729                      ;; Non-local lexical exit (someone closed over a
730                      ;; GO tag or BLOCK name).
731                      (let ((unique-tag (cons nil nil))
732                            values)
733                        (setf (eval-stack-local frame-ptr tag) unique-tag)
734                        (if (eq cont last-cont)
735                            (change-blocks (car (sb!c::block-succ block)))
736                            (setf node (sb!c::continuation-next cont)))
737                        (loop
738                          (multiple-value-setq (values block node cont last-cont)
739                            (catch unique-tag
740                              (internal-apply-loop node frame-ptr
741                                                   lambda args closure)))
742
743                          (when (eq values :fell-through)
744                            ;; We hit a %LEXICAL-EXIT-BREAKUP.
745                            ;; Interpreting state is set with MV-SETQ above.
746                            ;; Just get out of this branch and go on.
747                            (return))
748
749                          (unless (eq values :non-local-go)
750                            ;; We know we're non-locally exiting from a
751                            ;; BLOCK with values (saw a RETURN-FROM).
752                            (ecase (sb!c::continuation-info cont)
753                              (:single
754                               (eval-stack-push (car values)))
755                              ((:multiple :return)
756                               (eval-stack-push values))
757                              (:unused)))
758                          ;; Start interpreting again at the target, skipping
759                          ;; the %NLX-ENTRY block.
760                          (setf node
761                                (sb!c::continuation-next
762                                 (sb!c::block-start
763                                  (car (sb!c::block-succ block))))))))))))
764             (sb!c::exit
765              (maybe-trace-nodes node)
766              (let* ((incoming-values (sb!c::exit-value node))
767                     (values (if incoming-values (eval-stack-pop))))
768                (cond
769                 ((eq (sb!c::lambda-environment lambda)
770                      (sb!c::block-environment
771                       (sb!c::node-block (sb!c::exit-entry node))))
772                  ;; Local exit.
773                  ;; Fixup stack top and massage values for destination.
774                  (eval-stack-set-top
775                   (eval-stack-local frame-ptr
776                                     (sb!c:entry-node-info-st-top
777                                      (cdr (assoc (sb!c::exit-entry node)
778                                                  (sb!c:lambda-eval-info-entries
779                                                   (sb!c::lambda-info lambda)))))))
780                  (ecase (sb!c::continuation-info cont)
781                    (:single
782                     (assert incoming-values)
783                     (eval-stack-push (car values)))
784                    ((:multiple :return)
785                     (assert incoming-values)
786                     (eval-stack-push values))
787                    (:unused)))
788                 (t
789                  (let ((info (sb!c::find-nlx-info (sb!c::exit-entry node)
790                                                   cont)))
791                    (throw
792                     (svref closure
793                            (position info
794                                      (sb!c::environment-closure
795                                       (sb!c::node-environment node))
796                                      :test #'eq))
797                     (if incoming-values
798                         (values values (sb!c::nlx-info-target info) nil cont)
799                         (values :non-local-go (sb!c::nlx-info-target info)))))))))
800             (sb!c::creturn
801              (maybe-trace-nodes node)
802              (let ((values (eval-stack-pop)))
803                (eval-stack-set-top frame-ptr)
804                (return-from internal-apply-loop (values-list values))))
805             (sb!c::mv-combination
806              (maybe-trace-nodes node)
807              (combination-node :mv-call)))
808           ;; See function doc below.
809           (reference-this-var-to-keep-it-alive node)
810           (reference-this-var-to-keep-it-alive frame-ptr)
811           (reference-this-var-to-keep-it-alive closure)
812           (cond ((not (eq cont last-cont))
813                  (setf node (sb!c::continuation-next cont)))
814                 ;; Currently only the last node in a block causes this loop to
815                 ;; change blocks, so we never just go to the next node when
816                 ;; the current node's branch tried to change blocks.
817                 (set-block-p
818                  (change-blocks))
819                 (t
820                  ;; CIF nodes set the block for us, but other last
821                  ;; nodes do not.
822                  (change-blocks (car (sb!c::block-succ block)))))))))
823
824 ;;; This function allows a reference to a variable that the compiler cannot
825 ;;; easily eliminate as unnecessary. We use this at the end of the node
826 ;;; dispatch in INTERNAL-APPLY-LOOP to make sure the node variable has a
827 ;;; valid value. Each node branch tends to reference it at the beginning,
828 ;;; and then there is no reference but a set at the end; the compiler then
829 ;;; kills the variable between the reference in the dispatch branch and when
830 ;;; we set it at the end. The problem is that most error will occur in the
831 ;;; interpreter within one of these node dispatch branches.
832 (defun reference-this-var-to-keep-it-alive (node)
833   node)
834
835 ;;; This sets a sb!c::cset node's var to value, returning value. When var is
836 ;;; local, we have to compare its home environment to the current one, node's
837 ;;; environment. If they're the same, we check to see whether the var is
838 ;;; indirect, and store the value on the stack or in the value cell as
839 ;;; appropriate. Otherwise, var is a closure variable, and since we're
840 ;;; setting it, we know its location contains an indirect value object.
841 (defun set-leaf-value (node frame-ptr closure value)
842   (let ((var (sb!c::set-var node)))
843     (etypecase var
844       (sb!c::lambda-var
845        (set-leaf-value-lambda-var node var frame-ptr closure value))
846       (sb!c::global-var
847        (setf (symbol-value (sb!c::global-var-name var)) value)))))
848
849 ;;; This does SET-LEAF-VALUE for a lambda-var leaf. The debugger tools'
850 ;;; internals uses this also to set interpreted local variables.
851 (defun set-leaf-value-lambda-var (node var frame-ptr closure value)
852   (let ((env (sb!c::node-environment node)))
853     (cond ((not (eq (sb!c::lambda-environment (sb!c::lambda-var-home var))
854                     env))
855            (setf (indirect-value
856                   (svref closure
857                          (position var (sb!c::environment-closure env)
858                                    :test #'eq)))
859                  value))
860           ((sb!c::lambda-var-indirect var)
861            (setf (indirect-value
862                   (eval-stack-local frame-ptr (sb!c::lambda-var-info var)))
863                  value))
864           (t
865            (setf (eval-stack-local frame-ptr (sb!c::lambda-var-info var))
866                  value)))))
867
868 ;;; This figures out how to return a value for a ref node. Leaf is the ref's
869 ;;; structure that tells us about the value, and it is one of the following
870 ;;; types:
871 ;;;    constant   -- It knows its own value.
872 ;;;    global-var -- It's either a value or function reference. Get it right.
873 ;;;    local-var  -- This may on the stack or in the current closure, the
874 ;;;                  environment for the lambda INTERNAL-APPLY is currently
875 ;;;                  executing. If the leaf's home environment is the same
876 ;;;                  as the node's home environment, then the value is on the
877 ;;;                  stack, else it's in the closure since it came from another
878 ;;;                  environment. Whether the var comes from the stack or the
879 ;;;                  closure, it could have come from a closure, and it could
880 ;;;                  have been closed over for setting. When this happens, the
881 ;;;                  actual value is stored in an indirection object, so
882 ;;;                  indirect. See COMPUTE-CLOSURE for the description of
883 ;;;                  the structure of the closure argument to this function.
884 ;;;    functional -- This is a reference to an interpreted function that may
885 ;;;                  be passed or called anywhere. We return a real function
886 ;;;                  that calls INTERNAL-APPLY, closing over the leaf. We also
887 ;;;                  have to compute a closure, running environment, for the
888 ;;;                  lambda in case it references stuff in the current
889 ;;;                  environment. If the closure is empty and there is no
890 ;;;               functional environment, then we use
891 ;;;               MAKE-INTERPRETED-FUNCTION to make a cached translation.
892 ;;;               Since it is too late to lazily convert, we set up the
893 ;;;               INTERPRETED-FUNCTION to be already converted.
894 (defun leaf-value (node frame-ptr closure)
895   (let ((leaf (sb!c::ref-leaf node)))
896     (etypecase leaf
897       (sb!c::constant
898        (sb!c::constant-value leaf))
899       (sb!c::global-var
900        (locally (declare (optimize (safety 1)))
901          (if (eq (sb!c::global-var-kind leaf) :global-function)
902              (let ((name (sb!c::global-var-name leaf)))
903                (if (symbolp name)
904                    (symbol-function name)
905                    (fdefinition name)))
906              (symbol-value (sb!c::global-var-name leaf)))))
907       (sb!c::lambda-var
908        (leaf-value-lambda-var node leaf frame-ptr closure))
909       (sb!c::functional
910        (let* ((calling-closure (compute-closure node leaf frame-ptr closure))
911               (real-fun (sb!c::functional-entry-function leaf))
912               (arg-doc (sb!c::functional-arg-documentation real-fun)))
913          (cond ((sb!c:lambda-eval-info-function (sb!c::leaf-info leaf)))
914                ((and (zerop (length calling-closure))
915                      (null (sb!c::lexenv-functions
916                             (sb!c::functional-lexenv real-fun))))
917                 (let ((res (make-interpreted-function
918                             (sb!c::functional-inline-expansion real-fun))))
919                   (push res *interpreted-function-cache*)
920                   (setf (interpreted-function-definition res) leaf)
921                   (setf (interpreted-function-converted-once res) t)
922                   (setf (interpreted-function-arglist res) arg-doc)
923                   (setf (interpreted-function-%name res)
924                         (sb!c::leaf-name real-fun))
925                   (setf (sb!c:lambda-eval-info-function
926                          (sb!c::leaf-info leaf)) res)
927                   res))
928                (t
929                 (let ((res (%make-interpreted-function
930                             :definition leaf
931                             :%name (sb!c::leaf-name real-fun)
932                             :arglist arg-doc
933                             :closure calling-closure)))
934                   (setf (funcallable-instance-function res)
935                         #'(instance-lambda (&rest args)
936                             (declare (list args))
937                             (internal-apply
938                              (interpreted-function-definition res)
939                              (cons (length args) args)
940                              (interpreted-function-closure res))))
941                   res))))))))
942
943 ;;; This does LEAF-VALUE for a lambda-var leaf. The debugger tools' internals
944 ;;; uses this also to reference interpreted local variables.
945 (defun leaf-value-lambda-var (node leaf frame-ptr closure)
946   (let* ((env (sb!c::node-environment node))
947          (temp
948           (if (eq (sb!c::lambda-environment (sb!c::lambda-var-home leaf))
949                   env)
950               (eval-stack-local frame-ptr (sb!c::lambda-var-info leaf))
951               (svref closure
952                      (position leaf (sb!c::environment-closure env)
953                                :test #'eq)))))
954     (if (sb!c::lambda-var-indirect leaf)
955         (indirect-value temp)
956         temp)))
957
958 ;;; This computes a closure for a local call and for returned call'able closure
959 ;;; objects. Sometimes the closure is a simple-vector of no elements. Node
960 ;;; is either a reference node or a combination node. Leaf is either the leaf
961 ;;; of the reference node or the lambda to internally apply for the combination
962 ;;; node. Frame-ptr is the current frame pointer for fetching current values
963 ;;; to store in the closure. Closure is the current closure, the currently
964 ;;; interpreting lambda's closed over environment.
965 ;;;
966 ;;; A computed closure is a vector corresponding to the list of closure
967 ;;; variables described in an environment. The position of a lambda-var in
968 ;;; this closure list is the index into the closure vector of values.
969 ;;;
970 ;;; Functional-env is the environment description for leaf, the lambda for
971 ;;; which we're computing a closure. This environment describes which of
972 ;;; lambda's vars we find in lambda's closure when it's running, versus finding
973 ;;; them on the stack. For each lambda-var in the functional environment's
974 ;;; closure list, if the lambda-var's home environment is the current
975 ;;; environment, then get a value off the stack and store it in the closure
976 ;;; we're computing. Otherwise that lambda-var's value comes from somewhere
977 ;;; else, but we have it in our current closure, the environment we're running
978 ;;; in as we compute this new closure. Find this value the same way we do in
979 ;;; LEAF-VALUE, by finding the lambda-var's position in the current
980 ;;; environment's description of the current closure.
981 (defun compute-closure (node leaf frame-ptr closure)
982   (let* ((current-env (sb!c::node-environment node))
983          (current-closure-vars (sb!c::environment-closure current-env))
984          (functional-env (sb!c::lambda-environment leaf))
985          (functional-closure-vars (sb!c::environment-closure functional-env))
986          (functional-closure (make-array (length functional-closure-vars))))
987     (do ((vars functional-closure-vars (cdr vars))
988          (i 0 (1+ i)))
989         ((null vars))
990       (let ((ele (car vars)))
991         (setf (svref functional-closure i)
992               (etypecase ele
993                 (sb!c::lambda-var
994                  (if (eq (sb!c::lambda-environment (sb!c::lambda-var-home ele))
995                          current-env)
996                      (eval-stack-local frame-ptr (sb!c::lambda-var-info ele))
997                      (svref closure
998                             (position ele current-closure-vars
999                                       :test #'eq))))
1000                 (sb!c::nlx-info
1001                  (if (eq (sb!c::block-environment (sb!c::nlx-info-target ele))
1002                          current-env)
1003                      (eval-stack-local
1004                       frame-ptr
1005                       (sb!c:entry-node-info-nlx-tag
1006                        (cdr (assoc ;; entry node for non-local extent
1007                              (sb!c::cleanup-mess-up
1008                               (sb!c::nlx-info-cleanup ele))
1009                              (sb!c::lambda-eval-info-entries
1010                               (sb!c::lambda-info
1011                                ;; lambda INTERNAL-APPLY-LOOP tosses around.
1012                                (sb!c::environment-function
1013                                 (sb!c::node-environment node))))))))
1014                      (svref closure
1015                             (position ele current-closure-vars
1016                                       :test #'eq))))))))
1017     functional-closure))
1018
1019 ;;; INTERNAL-APPLY uses this to invoke a function from the interpreter's stack
1020 ;;; on some arguments also taken from the stack. When tail-p is non-nil,
1021 ;;; control does not return to INTERNAL-APPLY to further interpret the current
1022 ;;; IR1 lambda, so INTERNAL-INVOKE must clean up the current interpreter's
1023 ;;; stack frame.
1024 (defun internal-invoke (arg-count &optional tailp)
1025   (let ((args (eval-stack-args arg-count)) ;LET says this init form runs first.
1026         (fun (eval-stack-pop)))
1027     (when tailp (eval-stack-set-top tailp))
1028     (when *internal-apply-node-trace*
1029       (format t "(~S~{ ~S~})~%" fun args))
1030     (apply fun args)))
1031
1032 ;;; Almost just like INTERNAL-INVOKE. We call MV-EVAL-STACK-ARGS, and our
1033 ;;; function is in a list on the stack instead of simply on the stack.
1034 (defun mv-internal-invoke (arg-count &optional tailp)
1035   (let ((args (mv-eval-stack-args arg-count)) ;LET runs this init form first.
1036         (fun (car (eval-stack-pop))))
1037     (when tailp (eval-stack-set-top tailp))
1038     (when *internal-apply-node-trace*
1039       (format t "(~S~{ ~S~})~%" fun args))
1040     (apply fun args)))
1041
1042 ;;; This returns a list of the top arg-count elements on the interpreter's
1043 ;;; stack. This removes them from the stack.
1044 (defun eval-stack-args (arg-count)
1045   (let ((args nil))
1046     (dotimes (i arg-count args)
1047       (push (eval-stack-pop) args))))
1048
1049 ;;; This assumes the top count elements on interpreter's stack are lists. This
1050 ;;; returns a single list with all the elements from these lists.
1051 (defun mv-eval-stack-args (count)
1052   (if (= count 1)
1053       (eval-stack-pop)
1054       (let ((last (eval-stack-pop)))
1055         (dotimes (i (1- count))
1056           (let ((next (eval-stack-pop)))
1057             (setf last
1058                   (if next (nconc next last) last))))
1059         last)))
1060
1061 ;;; This stores lambda's vars, stack locals, from values popped off the stack.
1062 ;;; When a var has no references, the compiler computes IR1 such that the
1063 ;;; continuation delivering the value for the unreference var appears unused.
1064 ;;; Because of this, the interpreter drops the value on the floor instead of
1065 ;;; saving it on the stack for binding, so we only pop a value when the var has
1066 ;;; some reference. INTERNAL-APPLY uses this for sb!c::combination nodes
1067 ;;; representing LET's.
1068 ;;;
1069 ;;; When storing the local, if it is indirect, then someone closes over it for
1070 ;;; setting instead of just for referencing. We then store an indirection cell
1071 ;;; with the value, and the referencing code for locals knows how to get the
1072 ;;; actual value.
1073 (defun store-let-vars (lambda frame-ptr)
1074   (let* ((vars (sb!c::lambda-vars lambda))
1075          (args (eval-stack-args (count-if #'sb!c::leaf-refs vars))))
1076     (declare (list vars args))
1077     (dolist (v vars)
1078       (when (sb!c::leaf-refs v)
1079         (setf (eval-stack-local frame-ptr (sb!c::lambda-var-info v))
1080               (if (sb!c::lambda-var-indirect v)
1081                   (make-indirect-value-cell (pop args))
1082                   (pop args)))))))
1083
1084 ;;; This is similar to STORE-LET-VARS, but the values for the locals appear on
1085 ;;; the stack in a list due to forms that delivered multiple values to this
1086 ;;; lambda/let. Unlike STORE-LET-VARS, there is no control over the delivery
1087 ;;; of a value for an unreferenced var, so we drop the corresponding value on
1088 ;;; the floor when no one references it. INTERNAL-APPLY uses this for
1089 ;;; sb!c::mv-combination nodes representing LET's.
1090 (defun store-mv-let-vars (lambda frame-ptr count)
1091   (assert (= count 1))
1092   (let ((args (eval-stack-pop)))
1093     (dolist (v (sb!c::lambda-vars lambda))
1094       (if (sb!c::leaf-refs v)
1095           (setf (eval-stack-local frame-ptr (sb!c::lambda-var-info v))
1096                 (if (sb!c::lambda-var-indirect v)
1097                     (make-indirect-value-cell (pop args))
1098                     (pop args)))
1099           (pop args)))))
1100
1101 #|
1102 ;;; This stores lambda's vars, stack locals, from multiple values stored on the
1103 ;;; top of the stack in a list. Since these values arrived multiply, there is
1104 ;;; no control over the delivery of each value for an unreferenced var, so
1105 ;;; unlike STORE-LET-VARS, we have values for variables never used. We drop
1106 ;;; the value corresponding to an unreferenced var on the floor.
1107 ;;; INTERNAL-APPLY uses this for sb!c::mv-combination nodes representing LET's.
1108 ;;;
1109 ;;; IR1 represents variables bound from multiple values in a list in the
1110 ;;; opposite order of the values list. We use STORE-MV-LET-VARS-AUX to recurse
1111 ;;; down the vars list until we bottom out, storing values on the way back up
1112 ;;; the recursion. You must do this instead of NREVERSE'ing the args list, so
1113 ;;; when we run out of values, we store nil's in the correct lambda-vars.
1114 (defun store-mv-let-vars (lambda frame-ptr count)
1115   (assert (= count 1))
1116   (print  (sb!c::lambda-vars lambda))
1117   (store-mv-let-vars-aux frame-ptr (sb!c::lambda-vars lambda) (eval-stack-pop)))
1118 (defun store-mv-let-vars-aux (frame-ptr vars args)
1119   (if vars
1120       (let ((remaining-args (store-mv-let-vars-aux frame-ptr (cdr vars) args))
1121             (v (car vars)))
1122         (when (sb!c::leaf-refs v)
1123           (setf (eval-stack-local frame-ptr (sb!c::lambda-var-info v))
1124                 (if (sb!c::lambda-var-indirect v)
1125                     (make-indirect-value-cell (car remaining-args))
1126                     (car remaining-args))))
1127         (cdr remaining-args))
1128       args))
1129 |#