1 ;;;; a simple code walker
3 ;;;; The code which implements the macroexpansion environment
4 ;;;; manipulation mechanisms is in the first part of the file, the
5 ;;;; real walker follows it.
7 ;;;; This software is part of the SBCL system. See the README file for
10 ;;;; This software is derived from software originally released by Xerox
11 ;;;; Corporation. Copyright and release statements follow. Later modifications
12 ;;;; to the software are in the public domain and are provided with
13 ;;;; absolutely no warranty. See the COPYING and CREDITS files for more
16 ;;;; copyright information from original PCL sources:
18 ;;;; Copyright (c) 1985, 1986, 1987, 1988, 1989, 1990 Xerox Corporation.
19 ;;;; All rights reserved.
21 ;;;; Use and copying of this software and preparation of derivative works based
22 ;;;; upon this software are permitted. Any distribution of this software or
23 ;;;; derivative works must comply with all applicable United States export
26 ;;;; This software is made available AS IS, and Xerox Corporation makes no
27 ;;;; warranty about the software, its performance or its conformity to any
30 (in-package "SB!WALKER")
32 ;;;; forward references
34 (defvar *key-to-walker-environment*)
36 ;;;; environment hacking stuff, necessarily SBCL-specific
38 ;;; Here in the original PCL were implementations of the
39 ;;; implementation-specific environment hacking functions for each of
40 ;;; the implementations this walker had been ported to. This
41 ;;; functionality was originally factored out in order to make PCL
42 ;;; portable from one Common Lisp to another. As of 19981107, that
43 ;;; portability was fairly stale and (because of the scarcity of CLTL1
44 ;;; implementations and the strong interdependence of the rest of ANSI
45 ;;; Common Lisp on the CLOS system) fairly irrelevant. It was fairly
46 ;;; thoroughly put out of its misery by WHN in his quest to clean up
47 ;;; the system enough that it can be built from scratch using any ANSI
50 ;;; This code just hacks 'macroexpansion environments'. That is, it is
51 ;;; only concerned with the function binding of symbols in the
52 ;;; environment. The walker needs to be able to tell if the symbol
53 ;;; names a lexical macro or function, and it needs to be able to
54 ;;; build environments which contain lexical macro or function
55 ;;; bindings. It must be able, when walking a MACROLET, FLET or LABELS
56 ;;; form to construct an environment which reflects the bindings
57 ;;; created by that form. Note that the environment created does NOT
58 ;;; have to be sufficient to evaluate the body, merely to walk its
59 ;;; body. This means that definitions do not have to be supplied for
60 ;;; lexical functions, only the fact that that function is bound is
61 ;;; important. For macros, the macroexpansion function must be
64 ;;; This code is organized in a way that lets it work in
65 ;;; implementations that stack cons their environments. That is
66 ;;; reflected in the fact that the only operation that lets a user
67 ;;; build a new environment is a WITH-BODY macro which executes its
68 ;;; body with the specified symbol bound to the new environment. No
69 ;;; code in this walker or in PCL will hold a pointer to these
70 ;;; environments after the body returns. Other user code is free to do
71 ;;; so in implementations where it works, but that code is not
72 ;;; considered portable.
74 ;;; There are 3 environment hacking tools. One macro,
75 ;;; WITH-AUGMENTED-ENVIRONMENT, which is used to create new
76 ;;; environments, and two functions, ENVIRONMENT-FUNCTION and
77 ;;; ENVIRONMENT-MACRO, which are used to access the bindings of
78 ;;; existing environments
80 ;;; In SBCL, as in CMU CL before it, the environment is represented
81 ;;; with a structure that holds alists for the functional things,
82 ;;; variables, blocks, etc. Except for SYMBOL-MACROLET, only the
83 ;;; SB!C::LEXENV-FUNS slot is relevant. It holds: Alist (Name . What),
84 ;;; where What is either a functional (a local function) or a list
85 ;;; (MACRO . <function>) (a local macro, with the specifier expander.)
86 ;;; Note that Name may be a (SETF <name>) function. Accessors are
87 ;;; defined below, eg (ENV-WALK-FUNCTION ENV).
89 ;;; If WITH-AUGMENTED-ENVIRONMENT is called from WALKER-ENVIRONMENT-BIND
90 ;;; this code hides the WALKER version of an environment
91 ;;; inside the SB!C::LEXENV structure.
93 ;;; In CMUCL (and former SBCL), This used to be a list of lists of form
94 ;;; (<gensym-name> MACRO . #<interpreted-function>) in the :functions slot
96 ;;; This form was accepted by the compiler, but this was a crude hack,
97 ;;; because the <interpreted-function> was used as a structure to hold the
98 ;;; bits of interest, {function, form, declarations, lexical-variables},
99 ;;; a list, which was not really an interpreted function.
100 ;;; Instead this list was COERCEd to a #<FUNCTION ...>!
102 ;;; Instead, we now use a special sort of "function"-type for that
103 ;;; information, because the functions slot in SB!C::LEXENV is
104 ;;; supposed to have a list of <Name MACRO . #<function> elements.
105 ;;; So, now we hide our bits of interest in the walker-info slot in
106 ;;; our new BOGO-FUN.
108 ;;; MACROEXPAND-1 and SB!INT:EVAL-IN-LEXENV are the only SBCL
109 ;;; functions that get called with the constructed environment
112 (/show "walk.lisp 108")
114 (defmacro with-augmented-environment
115 ((new-env old-env &key functions macros) &body body)
116 `(let ((,new-env (with-augmented-environment-internal ,old-env
121 ;;; a unique tag to show that we're the intended caller of BOGO-FUN
122 (defvar *bogo-fun-magic-tag*
123 '(:bogo-fun-magic-tag))
125 ;;; The interface of BOGO-FUNs (previously implemented as
126 ;;; FUNCALLABLE-INSTANCEs) is just these two operations, so we can do
127 ;;; them with ordinary closures.
129 ;;; KLUDGE: BOGO-FUNs are sorta weird, and MNA and I have both hacked
130 ;;; on this code without quite figuring out what they're for. (He
131 ;;; changed them to work after some changes in the IR1 interpreter
132 ;;; made functions not be built lazily, and I changed them so that
133 ;;; they don't need FUNCALLABLE-INSTANCE stuff, so that the F-I stuff
134 ;;; can become less general.) There may be further simplifications or
135 ;;; clarifications which could be done. -- WHN 2001-10-19
136 (defun walker-info-to-bogo-fun (walker-info)
137 (lambda (magic-tag &rest rest)
138 (aver (not rest)) ; else someone is using me in an unexpected way
139 (aver (eql magic-tag *bogo-fun-magic-tag*)) ; else ditto
141 (defun bogo-fun-to-walker-info (bogo-fun)
142 (declare (type function bogo-fun))
143 (funcall bogo-fun *bogo-fun-magic-tag*))
145 (defun with-augmented-environment-internal (env funs macros)
146 ;; Note: In order to record the correct function definition, we
147 ;; would have to create an interpreted closure, but the
148 ;; WITH-NEW-DEFINITION macro down below makes no distinction between
149 ;; FLET and LABELS, so we have no idea what to use for the
150 ;; environment. So we just blow it off, 'cause anything real we do
151 ;; would be wrong. But we still have to make an entry so we can tell
152 ;; functions from macros.
153 (let ((lexenv (sb!kernel::coerce-to-lexenv env)))
156 :funs (append (mapcar (lambda (f)
158 (sb!c::make-functional :lexenv lexenv)))
164 *key-to-walker-environment*)
165 (walker-info-to-bogo-fun (cadr m))
166 (coerce (cadr m) 'function))))
169 (defun environment-function (env fn)
171 (let ((entry (assoc fn (sb!c::lexenv-funs env) :test #'equal)))
173 (sb!c::functional-p (cdr entry))
176 (defun environment-macro (env macro)
178 (let ((entry (assoc macro (sb!c::lexenv-funs env) :test #'eq)))
180 (eq (cadr entry) 'sb!c::macro)
181 (if (eq macro *key-to-walker-environment*)
182 (values (bogo-fun-to-walker-info (cddr entry)))
183 (values (function-lambda-expression (cddr entry))))))))
185 ;;;; other environment hacking, not so SBCL-specific as the
186 ;;;; environment hacking in the previous section
188 (defmacro with-new-definition-in-environment
189 ((new-env old-env macrolet/flet/labels-form) &body body)
190 (let ((functions (make-symbol "Functions"))
191 (macros (make-symbol "Macros")))
192 `(let ((,functions ())
194 (ecase (car ,macrolet/flet/labels-form)
196 (dolist (fn (cadr ,macrolet/flet/labels-form))
197 (push fn ,functions)))
199 (dolist (mac (cadr ,macrolet/flet/labels-form))
200 (push (list (car mac)
201 (convert-macro-to-lambda (cadr mac)
206 (with-augmented-environment
207 (,new-env ,old-env :functions ,functions :macros ,macros)
210 (defun convert-macro-to-lambda (llist body env &optional (name "dummy macro"))
211 (let ((gensym (make-symbol name)))
212 (eval-in-lexenv `(defmacro ,gensym ,llist ,@body)
213 (sb!c::make-restricted-lexenv env))
214 (macro-function gensym)))
216 ;;;; the actual walker
218 ;;; As the walker walks over the code, it communicates information to
219 ;;; itself about the walk. This information includes the walk
220 ;;; function, variable bindings, declarations in effect etc. This
221 ;;; information is inherently lexical, so the walker passes it around
222 ;;; in the actual environment the walker passes to macroexpansion
223 ;;; functions. This is what makes the NESTED-WALK-FORM facility work
225 (defmacro walker-environment-bind ((var env &rest key-args)
227 `(with-augmented-environment
228 (,var ,env :macros (walker-environment-bind-1 ,env ,.key-args))
231 (defvar *key-to-walker-environment* (gensym))
233 (defun env-lock (env)
234 (environment-macro env *key-to-walker-environment*))
236 (defun walker-environment-bind-1 (env &key (walk-function nil wfnp)
238 (declarations nil decp)
239 (lexical-variables nil lexp))
240 (let ((lock (environment-macro env *key-to-walker-environment*)))
242 (list *key-to-walker-environment*
243 (list (if wfnp walk-function (car lock))
244 (if wfop walk-form (cadr lock))
245 (if decp declarations (caddr lock))
246 (if lexp lexical-variables (cadddr lock)))))))
248 (defun env-walk-function (env)
249 (car (env-lock env)))
251 (defun env-walk-form (env)
252 (cadr (env-lock env)))
254 (defun env-declarations (env)
255 (caddr (env-lock env)))
257 (defun env-lexical-variables (env)
258 (cadddr (env-lock env)))
260 (defun note-declaration (declaration env)
261 (push declaration (caddr (env-lock env))))
263 (defun note-lexical-binding (thing env)
264 (push (list thing :lexical-var) (cadddr (env-lock env))))
266 (defun var-lexical-p (var env)
267 (let ((entry (member var (env-lexical-variables env) :key #'car)))
268 (when (eq (cadar entry) :lexical-var)
271 (defun variable-symbol-macro-p (var env)
272 (let ((entry (member var (env-lexical-variables env) :key #'car)))
273 (when (eq (cadar entry) 'sb!sys:macro)
276 (defvar *var-declarations* '(special))
278 (defun var-declaration (declaration var env)
279 (if (not (member declaration *var-declarations*))
280 (error "~S is not a recognized variable declaration." declaration)
281 (let ((id (or (var-lexical-p var env) var)))
282 (dolist (decl (env-declarations env))
283 (when (and (eq (car decl) declaration)
287 (defun var-special-p (var env)
288 (or (not (null (var-declaration 'special var env)))
289 (var-globally-special-p var)))
291 (defun var-globally-special-p (symbol)
292 (eq (info :variable :kind symbol) :special))
294 ;;;; handling of special forms
296 ;;; Here are some comments from the original PCL on the difficulty of
297 ;;; doing this portably across different CLTL1 implementations. This
298 ;;; is no longer directly relevant because this code now only runs on
299 ;;; SBCL, but the comments are retained for culture: they might help
300 ;;; explain some of the design decisions which were made in the code.
304 ;;; The set of special forms is purposely kept very small because
305 ;;; any program analyzing program (read code walker) must have
306 ;;; special knowledge about every type of special form. Such a
307 ;;; program needs no special knowledge about macros...
309 ;;; So all we have to do here is a define a way to store and retrieve
310 ;;; templates which describe how to walk the 24 special forms and we
313 ;;; Well, its a nice concept, and I have to admit to being naive
314 ;;; enough that I believed it for a while, but not everyone takes
315 ;;; having only 24 special forms as seriously as might be nice. There
316 ;;; are (at least) 3 ways to lose:
318 ;;; 1 - Implementation x implements a Common Lisp special form as
319 ;;; a macro which expands into a special form which:
320 ;;; - Is a common lisp special form (not likely)
321 ;;; - Is not a common lisp special form (on the 3600 IF --> COND).
323 ;;; * We can save ourselves from this case (second subcase really)
324 ;;; by checking to see whether there is a template defined for
325 ;;; something before we check to see whether we can macroexpand it.
327 ;;; 2 - Implementation x implements a Common Lisp macro as a special form.
329 ;;; * This is a screw, but not so bad, we save ourselves from it by
330 ;;; defining extra templates for the macros which are *likely* to
331 ;;; be implemented as special forms. [Note: As of sbcl-0.6.9, these
332 ;;; extra templates have been deleted, since this is not a problem
333 ;;; in SBCL and we no longer try to make this walker portable
334 ;;; across other possibly-broken CL implementations.]
336 ;;; 3 - Implementation x has a special form which is not on the list of
337 ;;; Common Lisp special forms.
339 ;;; * This is a bad sort of a screw and happens more than I would
340 ;;; like to think, especially in the implementations which provide
341 ;;; more than just Common Lisp (3600, Xerox etc.).
342 ;;; The fix is not terribly satisfactory, but will have to do for
343 ;;; now. There is a hook in get walker-template which can get a
344 ;;; template from the implementation's own walker. That template
345 ;;; has to be converted, and so it may be that the right way to do
346 ;;; this would actually be for that implementation to provide an
347 ;;; interface to its walker which looks like the interface to this
350 (defmacro get-walker-template-internal (x)
351 `(get ,x 'walker-template))
353 (defmacro define-walker-template (name
354 &optional (template '(nil repeat (eval))))
355 `(eval-when (:load-toplevel :execute)
356 (setf (get-walker-template-internal ',name) ',template)))
358 (defun get-walker-template (x)
360 (get-walker-template-internal x))
361 ((and (listp x) (eq (car x) 'lambda))
362 '(lambda repeat (eval)))
364 (error "can't get template for ~S" x))))
366 ;;;; the actual templates
368 ;;; ANSI special forms
369 (define-walker-template block (nil nil repeat (eval)))
370 (define-walker-template catch (nil eval repeat (eval)))
371 (define-walker-template declare walk-unexpected-declare)
372 (define-walker-template eval-when (nil quote repeat (eval)))
373 (define-walker-template flet walk-flet)
374 (define-walker-template function (nil call))
375 (define-walker-template go (nil quote))
376 (define-walker-template if walk-if)
377 (define-walker-template labels walk-labels)
378 (define-walker-template lambda walk-lambda)
379 (define-walker-template let walk-let)
380 (define-walker-template let* walk-let*)
381 (define-walker-template locally walk-locally)
382 (define-walker-template macrolet walk-macrolet)
383 (define-walker-template multiple-value-call (nil eval repeat (eval)))
384 (define-walker-template multiple-value-prog1 (nil return repeat (eval)))
385 (define-walker-template multiple-value-setq walk-multiple-value-setq)
386 (define-walker-template multiple-value-bind walk-multiple-value-bind)
387 (define-walker-template progn (nil repeat (eval)))
388 (define-walker-template progv (nil eval eval repeat (eval)))
389 (define-walker-template quote (nil quote))
390 (define-walker-template return-from (nil quote repeat (return)))
391 (define-walker-template setq walk-setq)
392 (define-walker-template symbol-macrolet walk-symbol-macrolet)
393 (define-walker-template tagbody walk-tagbody)
394 (define-walker-template the (nil quote eval))
395 (define-walker-template throw (nil eval eval))
396 (define-walker-template unwind-protect (nil return repeat (eval)))
398 ;;; SBCL-only special forms
399 (define-walker-template sb!ext:truly-the (nil quote eval))
401 (defvar *walk-form-expand-macros-p* nil)
403 (defun walk-form (form
404 &optional environment
406 (lambda (subform context env)
407 (declare (ignore context env))
409 (walker-environment-bind (new-env environment :walk-function walk-function)
410 (walk-form-internal form :eval new-env)))
412 ;;; WALK-FORM-INTERNAL is the main driving function for the code
413 ;;; walker. It takes a form and the current context and walks the form
414 ;;; calling itself or the appropriate template recursively.
416 ;;; "It is recommended that a program-analyzing-program process a form
417 ;;; that is a list whose car is a symbol as follows:
419 ;;; 1. If the program has particular knowledge about the symbol,
420 ;;; process the form using special-purpose code. All of the
421 ;;; standard special forms should fall into this category.
422 ;;; 2. Otherwise, if MACRO-FUNCTION is true of the symbol apply
423 ;;; either MACROEXPAND or MACROEXPAND-1 and start over.
424 ;;; 3. Otherwise, assume it is a function call. "
425 (defun walk-form-internal (form context env)
426 ;; First apply the walk-function to perform whatever translation
427 ;; the user wants to this form. If the second value returned
428 ;; by walk-function is T then we don't recurse...
430 (multiple-value-bind (newform walk-no-more-p)
431 (funcall (env-walk-function env) form context env)
434 (walk-no-more-p newform)
435 ((not (eq form newform))
436 (walk-form-internal newform context env))
437 ((not (consp newform))
438 (let ((symmac (car (variable-symbol-macro-p newform env))))
440 (let ((newnewform (walk-form-internal (cddr symmac)
443 (if (eq newnewform (cddr symmac))
444 (if *walk-form-expand-macros-p* newnewform newform)
448 (let* ((fn (car newform))
449 (template (get-walker-template fn)))
451 (if (symbolp template)
452 (funcall template newform context env)
453 (walk-template newform template context env))
454 (multiple-value-bind (newnewform macrop)
455 (walker-environment-bind
456 (new-env env :walk-form newform)
457 (sb-xc:macroexpand-1 newform new-env))
460 (let ((newnewnewform (walk-form-internal newnewform
463 (if (eq newnewnewform newnewform)
464 (if *walk-form-expand-macros-p* newnewform newform)
468 (special-operator-p fn))
469 ;; This shouldn't happen, since this walker is now
470 ;; maintained as part of SBCL, so it should know
471 ;; about all the special forms that SBCL knows
473 (bug "unexpected special form ~S" fn))
475 ;; Otherwise, walk the form as if it's just a
476 ;; standard function call using a template for
477 ;; standard function call.
479 newnewform '(call repeat (eval)) context env))))))))))))
481 (defun walk-template (form template context env)
484 ((eval function test effect return)
485 (walk-form-internal form :eval env))
488 (walk-form-internal form :set env))
490 (cond ((legal-fun-name-p form)
492 (t (walk-form-internal form context env)))))
495 (walk-template-handle-repeat form
497 ;; For the case where nothing
498 ;; happens after the repeat
499 ;; optimize away the call to
501 (if (null (cddr template))
503 (nthcdr (- (length form)
511 (if (if (listp (cadr template))
512 (eval (cadr template))
513 (funcall (cadr template) form))
519 (walk-template form (cadr template) context env))
521 (cond ((atom form) form)
524 (car form) (car template) context env)
526 (cdr form) (cdr template) context env))))))))
528 (defun walk-template-handle-repeat (form template stop-form context env)
529 (if (eq form stop-form)
530 (walk-template form (cdr template) context env)
531 (walk-template-handle-repeat-1 form
538 (defun walk-template-handle-repeat-1 (form template repeat-template
539 stop-form context env)
540 (cond ((null form) ())
542 (if (null repeat-template)
543 (walk-template stop-form (cdr template) context env)
544 (error "while handling code walker REPEAT:
545 ~%ran into STOP while still in REPEAT template")))
546 ((null repeat-template)
547 (walk-template-handle-repeat-1
548 form template (car template) stop-form context env))
551 (walk-template (car form) (car repeat-template) context env)
552 (walk-template-handle-repeat-1 (cdr form)
554 (cdr repeat-template)
559 (defun walk-repeat-eval (form env)
562 (walk-form-internal (car form) :eval env)
563 (walk-repeat-eval (cdr form) env))))
565 (defun recons (x car cdr)
566 (if (or (not (eq (car x) car))
567 (not (eq (cdr x) cdr)))
571 (defun relist (x &rest args)
574 (relist-internal x args nil)))
576 (defun relist* (x &rest args)
577 (relist-internal x args t))
579 (defun relist-internal (x args *p)
580 (if (null (cdr args))
583 (recons x (car args) nil))
586 (relist-internal (cdr x) (cdr args) *p))))
590 (defun walk-declarations (body fn env
591 &optional doc-string-p declarations old-body
592 &aux (form (car body)) macrop new-form)
593 (cond ((and (stringp form) ;might be a doc string
594 (cdr body) ;isn't the returned value
595 (null doc-string-p) ;no doc string yet
596 (null declarations)) ;no declarations yet
599 (walk-declarations (cdr body) fn env t)))
600 ((and (listp form) (eq (car form) 'declare))
601 ;; We got ourselves a real live declaration. Record it, look
603 (dolist (declaration (cdr form))
604 (let ((type (car declaration))
605 (name (cadr declaration))
606 (args (cddr declaration)))
607 (if (member type *var-declarations*)
608 (note-declaration `(,type
609 ,(or (var-lexical-p name env) name)
612 (note-declaration declaration env))
613 (push declaration declarations)))
617 (cdr body) fn env doc-string-p declarations)))
620 (null (get-walker-template (car form)))
622 (multiple-value-setq (new-form macrop)
623 (sb-xc:macroexpand-1 form env))
625 ;; This form was a call to a macro. Maybe it expanded
626 ;; into a declare? Recurse to find out.
627 (walk-declarations (recons body new-form (cdr body))
628 fn env doc-string-p declarations
631 ;; Now that we have walked and recorded the declarations,
632 ;; call the function our caller provided to expand the body.
633 ;; We call that function rather than passing the real-body
634 ;; back, because we are RECONSING up the new body.
635 (funcall fn (or old-body body) env))))
637 (defun walk-unexpected-declare (form context env)
638 (declare (ignore context env))
639 (warn "encountered ~S ~_in a place where a DECLARE was not expected"
643 (defun walk-arglist (arglist context env &optional (destructuringp nil)
645 (cond ((null arglist) ())
646 ((symbolp (setq arg (car arglist)))
647 (or (member arg lambda-list-keywords)
648 (note-lexical-binding arg env))
651 (walk-arglist (cdr arglist)
656 lambda-list-keywords))))))
658 (prog1 (recons arglist
660 (walk-arglist arg context env destructuringp)
663 (walk-form-internal (cadr arg) :eval env)
665 (walk-arglist (cdr arglist) context env nil))
666 (if (symbolp (car arg))
667 (note-lexical-binding (car arg) env)
668 (note-lexical-binding (cadar arg) env))
669 (or (null (cddr arg))
670 (not (symbolp (caddr arg)))
671 (note-lexical-binding (caddr arg) env))))
673 (error "can't understand something in the arglist ~S" arglist))))
675 (defun walk-let (form context env)
676 (walk-let/let* form context env nil))
678 (defun walk-let* (form context env)
679 (walk-let/let* form context env t))
681 (defun walk-let/let* (form context old-env sequentialp)
682 (walker-environment-bind (new-env old-env)
683 (let* ((let/let* (car form))
684 (bindings (cadr form))
687 (walk-bindings-1 bindings
693 (walk-declarations body #'walk-repeat-eval new-env)))
695 form let/let* walked-bindings walked-body))))
697 (defun walk-locally (form context env)
698 (declare (ignore context))
699 (let* ((locally (car form))
702 (walk-declarations body #'walk-repeat-eval env)))
704 form locally walked-body)))
706 (defun walk-let-if (form context env)
707 (let ((test (cadr form))
708 (bindings (caddr form))
712 (declare (special ,@(mapcar (lambda (x) (if (listp x) (car x) x))
714 (flet ((.let-if-dummy. () ,@body))
716 (let ,bindings (.let-if-dummy.))
721 (defun walk-multiple-value-setq (form context env)
722 (let ((vars (cadr form)))
723 (if (some (lambda (var)
724 (variable-symbol-macro-p var env))
726 (let* ((temps (mapcar (lambda (var)
727 (declare (ignore var))
730 (sets (mapcar (lambda (var temp) `(setq ,var ,temp))
733 (expanded `(multiple-value-bind ,temps ,(caddr form)
735 (walked (walk-form-internal expanded context env)))
736 (if (eq walked expanded)
739 (walk-template form '(nil (repeat (set)) eval) context env))))
741 (defun walk-multiple-value-bind (form context old-env)
742 (walker-environment-bind (new-env old-env)
743 (let* ((mvb (car form))
744 (bindings (cadr form))
745 (mv-form (walk-template (caddr form) 'eval context old-env))
751 (lambda (real-body real-env)
752 (setq walked-bindings
753 (walk-bindings-1 bindings
758 (walk-repeat-eval real-body real-env))
760 (relist* form mvb walked-bindings mv-form walked-body))))
762 (defun walk-bindings-1 (bindings old-env new-env context sequentialp)
764 (let ((binding (car bindings)))
766 (if (symbolp binding)
768 (note-lexical-binding binding new-env))
769 (prog1 (relist* binding
771 (walk-form-internal (cadr binding)
776 ;; Save cddr for DO/DO*; it is
777 ;; the next value form. Don't
778 ;; walk it now, though.
780 (note-lexical-binding (car binding) new-env)))
781 (walk-bindings-1 (cdr bindings)
787 (defun walk-bindings-2 (bindings walked-bindings context env)
789 (let ((binding (car bindings))
790 (walked-binding (car walked-bindings)))
792 (if (symbolp binding)
796 (cadr walked-binding)
797 (walk-template (cddr binding)
801 (walk-bindings-2 (cdr bindings)
802 (cdr walked-bindings)
806 (defun walk-lambda (form context old-env)
807 (walker-environment-bind (new-env old-env)
808 (let* ((arglist (cadr form))
810 (walked-arglist (walk-arglist arglist context new-env))
812 (walk-declarations body #'walk-repeat-eval new-env)))
818 (defun walk-setq (form context env)
820 (let* ((expanded (let ((rforms nil)
822 (loop (when (null tail) (return (nreverse rforms)))
823 (let ((var (pop tail)) (val (pop tail)))
824 (push `(setq ,var ,val) rforms)))))
825 (walked (walk-repeat-eval expanded env)))
826 (if (eq expanded walked)
829 (let* ((var (cadr form))
831 (symmac (car (variable-symbol-macro-p var env))))
833 (let* ((expanded `(setf ,(cddr symmac) ,val))
834 (walked (walk-form-internal expanded context env)))
835 (if (eq expanded walked)
839 (walk-form-internal var :set env)
840 (walk-form-internal val :eval env))))))
842 (defun walk-symbol-macrolet (form context old-env)
843 (declare (ignore context))
844 (let* ((bindings (cadr form))
846 (walker-environment-bind
849 (append (mapcar (lambda (binding)
851 sb!sys:macro . ,(cadr binding)))
853 (env-lexical-variables old-env)))
854 (relist* form 'symbol-macrolet bindings
855 (walk-declarations body #'walk-repeat-eval new-env)))))
857 (defun walk-tagbody (form context env)
858 (recons form (car form) (walk-tagbody-1 (cdr form) context env)))
860 (defun walk-tagbody-1 (form context env)
863 (walk-form-internal (car form)
864 (if (symbolp (car form)) 'quote context)
866 (walk-tagbody-1 (cdr form) context env))))
868 (defun walk-macrolet (form context old-env)
869 (walker-environment-bind (macro-env
871 :walk-function (env-walk-function old-env))
872 (labels ((walk-definitions (definitions)
874 (let ((definition (car definitions)))
878 (walk-arglist (cadr definition)
882 (walk-declarations (cddr definition)
885 (walk-definitions (cdr definitions)))))))
886 (with-new-definition-in-environment (new-env old-env form)
889 (walk-definitions (cadr form))
890 (walk-declarations (cddr form)
894 (defun walk-flet (form context old-env)
895 (labels ((walk-definitions (definitions)
896 (if (null definitions)
899 (walk-lambda (car definitions) context old-env)
900 (walk-definitions (cdr definitions))))))
904 (walk-definitions (cadr form))
905 (with-new-definition-in-environment (new-env old-env form)
906 (walk-declarations (cddr form)
910 (defun walk-labels (form context old-env)
911 (with-new-definition-in-environment (new-env old-env form)
912 (labels ((walk-definitions (definitions)
913 (if (null definitions)
916 (walk-lambda (car definitions) context new-env)
917 (walk-definitions (cdr definitions))))))
921 (walk-definitions (cadr form))
922 (walk-declarations (cddr form)
926 (defun walk-if (form context env)
927 (destructuring-bind (if predicate arm1 &optional arm2) form
928 (declare (ignore if)) ; should be 'IF
931 (walk-form-internal predicate context env)
932 (walk-form-internal arm1 context env)
933 (walk-form-internal arm2 context env))))
938 ;;; Here are some examples of the kinds of things you should be able
939 ;;; to do with your implementation of the macroexpansion environment
940 ;;; hacking mechanism.
942 ;;; WITH-LEXICAL-MACROS is kind of like MACROLET, but it only takes
943 ;;; names of the macros and actual macroexpansion functions to use to
944 ;;; macroexpand them. The win about that is that for macros which want
945 ;;; to wrap several MACROLETs around their body, they can do this but
946 ;;; have the macroexpansion functions be compiled. See the WITH-RPUSH
949 ;;; If the implementation had a special way of communicating the
950 ;;; augmented environment back to the evaluator that would be totally
951 ;;; great. It would mean that we could just augment the environment
952 ;;; then pass control back to the implementations own compiler or
953 ;;; interpreter. We wouldn't have to call the actual walker. That
954 ;;; would make this much faster. Since the principal client of this is
955 ;;; defmethod it would make compiling defmethods faster and that would
956 ;;; certainly be a win.
958 (defmacro with-lexical-macros (macros &body body &environment old-env)
959 (with-augmented-environment (new-env old-env :macros macros)
960 (walk-form (cons 'progn body) :environment new-env)))
962 (defun expand-rpush (form env)
963 (declare (ignore env))
964 `(push ,(caddr form) ,(cadr form)))
966 (defmacro with-rpush (&body body)
967 `(with-lexical-macros ,(list (list 'rpush #'expand-rpush)) ,@body))