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