1 ;;;; a simple code walker for PCL
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 ;;;; environment hacking stuff, necessarily SBCL-specific
34 ;;; Here in the original PCL were implementations of the
35 ;;; implementation-specific environment hacking functions for each of
36 ;;; the implementations this walker had been ported to. This
37 ;;; functionality was originally factored out in order to make PCL
38 ;;; portable from one Common Lisp to another. As of 19981107, that
39 ;;; portability was fairly stale and (because of the scarcity of CLTL1
40 ;;; implementations and the strong interdependence of the rest of ANSI
41 ;;; Common Lisp on the CLOS system) fairly irrelevant. It was fairly
42 ;;; thoroughly put out of its misery by WHN in his quest to clean up
43 ;;; the system enough that it can be built from scratch using any ANSI
46 ;;; This code just hacks 'macroexpansion environments'. That is, it is
47 ;;; only concerned with the function binding of symbols in the
48 ;;; environment. The walker needs to be able to tell if the symbol
49 ;;; names a lexical macro or function, and it needs to be able to
50 ;;; build environments which contain lexical macro or function
51 ;;; bindings. It must be able, when walking a MACROLET, FLET or LABELS
52 ;;; form to construct an environment which reflects the bindings
53 ;;; created by that form. Note that the environment created does NOT
54 ;;; have to be sufficient to evaluate the body, merely to walk its
55 ;;; body. This means that definitions do not have to be supplied for
56 ;;; lexical functions, only the fact that that function is bound is
57 ;;; important. For macros, the macroexpansion function must be
60 ;;; This code is organized in a way that lets it work in
61 ;;; implementations that stack cons their environments. That is
62 ;;; reflected in the fact that the only operation that lets a user
63 ;;; build a new environment is a WITH-BODY macro which executes its
64 ;;; body with the specified symbol bound to the new environment. No
65 ;;; code in this walker or in PCL will hold a pointer to these
66 ;;; environments after the body returns. Other user code is free to do
67 ;;; so in implementations where it works, but that code is not
68 ;;; considered portable.
70 ;;; There are 3 environment hacking tools. One macro,
71 ;;; WITH-AUGMENTED-ENVIRONMENT, which is used to create new
72 ;;; environments, and two functions, ENVIRONMENT-FUNCTION and
73 ;;; ENVIRONMENT-MACRO, which are used to access the bindings of
74 ;;; existing environments
76 ;;; In SBCL, as in CMU CL before it, the environment is represented
77 ;;; with a structure that holds alists for the functional things,
78 ;;; variables, blocks, etc. Except for SYMBOL-MACROLET, only the
79 ;;; SB-C::LEXENV-FUNS slot is relevant. It holds: Alist (Name . What),
80 ;;; where What is either a functional (a local function) or a list
81 ;;; (MACRO . <function>) (a local macro, with the specifier expander.)
82 ;;; Note that Name may be a (SETF <name>) function. Accessors are
83 ;;; defined below, eg (ENV-WALK-FUNCTION ENV).
85 ;;; If WITH-AUGMENTED-ENVIRONMENT is called from WALKER-ENVIRONMENT-BIND
86 ;;; this code hides the WALKER version of an environment
87 ;;; inside the SB-C::LEXENV structure.
89 ;;; In CMUCL (and former SBCL), This used to be a list of lists of form
90 ;;; (<gensym-name> MACRO . #<interpreted-function>) in the :functions slot
92 ;;; This form was accepted by the compiler, but this was a crude hack,
93 ;;; because the <interpreted-function> was used as a structure to hold the
94 ;;; bits of interest, {function, form, declarations, lexical-variables},
95 ;;; a list, which was not really an interpreted function.
96 ;;; Instead this list was COERCEd to a #<FUNCTION ...>!
98 ;;; Instead, we now use a special sort of "function"-type for that
99 ;;; information, because the functions slot in SB-C::LEXENV is
100 ;;; supposed to have a list of <Name MACRO . #<function> elements.
101 ;;; So, now we hide our bits of interest in the walker-info slot in
102 ;;; our new BOGO-FUN.
104 ;;; MACROEXPAND-1 is the only SBCL function that gets called with the
105 ;;; constructed environment argument.
107 (/show "walk.lisp 108")
109 (defmacro with-augmented-environment
110 ((new-env old-env &key functions macros) &body body)
111 `(let ((,new-env (with-augmented-environment-internal ,old-env
116 ;;; a unique tag to show that we're the intended caller of BOGO-FUN
117 (defvar *bogo-fun-magic-tag*
118 '(:bogo-fun-magic-tag))
120 ;;; The interface of BOGO-FUNs (previously implemented as
121 ;;; FUNCALLABLE-INSTANCEs) is just these two operations, so we can do
122 ;;; them with ordinary closures.
124 ;;; KLUDGE: BOGO-FUNs are sorta weird, and MNA and I have both hacked
125 ;;; on this code without quite figuring out what they're for. (He
126 ;;; changed them to work after some changes in the IR1 interpreter
127 ;;; made functions not be built lazily, and I changed them so that
128 ;;; they don't need FUNCALLABLE-INSTANCE stuff, so that the F-I stuff
129 ;;; can become less general.) There may be further simplifications or
130 ;;; clarifications which could be done. -- WHN 2001-10-19
131 (defun walker-info-to-bogo-fun (walker-info)
132 (lambda (magic-tag &rest rest)
133 (aver (not rest)) ; else someone is using me in an unexpected way
134 (aver (eql magic-tag *bogo-fun-magic-tag*)) ; else ditto
136 (defun bogo-fun-to-walker-info (bogo-fun)
137 (declare (type function bogo-fun))
138 (funcall bogo-fun *bogo-fun-magic-tag*))
140 (defun with-augmented-environment-internal (env funs macros)
141 ;; Note: In order to record the correct function definition, we
142 ;; would have to create an interpreted closure, but the
143 ;; WITH-NEW-DEFINITION macro down below makes no distinction between
144 ;; FLET and LABELS, so we have no idea what to use for the
145 ;; environment. So we just blow it off, 'cause anything real we do
146 ;; would be wrong. But we still have to make an entry so we can tell
147 ;; functions from macros.
148 (let ((lexenv (sb-kernel::coerce-to-lexenv env)))
151 :funs (append (mapcar (lambda (f)
153 (sb-c::make-functional :lexenv lexenv)))
159 *key-to-walker-environment*)
160 (walker-info-to-bogo-fun (cadr m))
161 (coerce (cadr m) 'function))))
164 (defun environment-function (env fn)
166 (let ((entry (assoc fn (sb-c::lexenv-funs env) :test #'equal)))
168 (sb-c::functional-p (cdr entry))
171 (defun environment-macro (env macro)
173 (let ((entry (assoc macro (sb-c::lexenv-funs env) :test #'eq)))
175 (eq (cadr entry) 'sb-c::macro)
176 (if (eq macro *key-to-walker-environment*)
177 (values (bogo-fun-to-walker-info (cddr entry)))
178 (values (function-lambda-expression (cddr entry))))))))
180 ;;;; other environment hacking, not so SBCL-specific as the
181 ;;;; environment hacking in the previous section
183 (defmacro with-new-definition-in-environment
184 ((new-env old-env macrolet/flet/labels-form) &body body)
185 (let ((functions (make-symbol "Functions"))
186 (macros (make-symbol "Macros")))
187 `(let ((,functions ())
189 (ecase (car ,macrolet/flet/labels-form)
191 (dolist (fn (cadr ,macrolet/flet/labels-form))
192 (push fn ,functions)))
194 (dolist (mac (cadr ,macrolet/flet/labels-form))
195 (push (list (car mac)
196 (convert-macro-to-lambda (cadr mac)
200 (with-augmented-environment
201 (,new-env ,old-env :functions ,functions :macros ,macros)
204 (defun convert-macro-to-lambda (llist body &optional (name "dummy macro"))
205 (let ((gensym (make-symbol name)))
206 (eval `(defmacro ,gensym ,llist ,@body))
207 (macro-function gensym)))
209 ;;;; the actual walker
211 ;;; As the walker walks over the code, it communicates information to
212 ;;; itself about the walk. This information includes the walk
213 ;;; function, variable bindings, declarations in effect etc. This
214 ;;; information is inherently lexical, so the walker passes it around
215 ;;; in the actual environment the walker passes to macroexpansion
216 ;;; functions. This is what makes the NESTED-WALK-FORM facility work
218 (defmacro walker-environment-bind ((var env &rest key-args)
220 `(with-augmented-environment
221 (,var ,env :macros (walker-environment-bind-1 ,env ,.key-args))
224 (defvar *key-to-walker-environment* (gensym))
226 (defun env-lock (env)
227 (environment-macro env *key-to-walker-environment*))
229 (defun walker-environment-bind-1 (env &key (walk-function nil wfnp)
231 (declarations nil decp)
232 (lexical-variables nil lexp))
233 (let ((lock (environment-macro env *key-to-walker-environment*)))
235 (list *key-to-walker-environment*
236 (list (if wfnp walk-function (car lock))
237 (if wfop walk-form (cadr lock))
238 (if decp declarations (caddr lock))
239 (if lexp lexical-variables (cadddr lock)))))))
241 (defun env-walk-function (env)
242 (car (env-lock env)))
244 (defun env-walk-form (env)
245 (cadr (env-lock env)))
247 (defun env-declarations (env)
248 (caddr (env-lock env)))
250 (defun env-lexical-variables (env)
251 (cadddr (env-lock env)))
253 (defun note-declaration (declaration env)
254 (push declaration (caddr (env-lock env))))
256 (defun note-lexical-binding (thing env)
257 (push (list thing :lexical-var) (cadddr (env-lock env))))
259 (defun var-lexical-p (var env)
260 (let ((entry (member var (env-lexical-variables env) :key #'car)))
261 (when (eq (cadar entry) :lexical-var)
264 (defun variable-symbol-macro-p (var env)
265 (let ((entry (member var (env-lexical-variables env) :key #'car)))
266 (when (eq (cadar entry) :macro)
269 (defvar *var-declarations* '(special))
271 (defun var-declaration (declaration var env)
272 (if (not (member declaration *var-declarations*))
273 (error "~S is not a recognized variable declaration." declaration)
274 (let ((id (or (var-lexical-p var env) var)))
275 (dolist (decl (env-declarations env))
276 (when (and (eq (car decl) declaration)
280 (defun var-special-p (var env)
281 (or (not (null (var-declaration 'special var env)))
282 (var-globally-special-p var)))
284 (defun var-globally-special-p (symbol)
285 (eq (info :variable :kind symbol) :special))
287 ;;;; handling of special forms
289 ;;; Here are some comments from the original PCL on the difficulty of
290 ;;; doing this portably across different CLTL1 implementations. This
291 ;;; is no longer directly relevant because this code now only runs on
292 ;;; SBCL, but the comments are retained for culture: they might help
293 ;;; explain some of the design decisions which were made in the code.
297 ;;; The set of special forms is purposely kept very small because
298 ;;; any program analyzing program (read code walker) must have
299 ;;; special knowledge about every type of special form. Such a
300 ;;; program needs no special knowledge about macros...
302 ;;; So all we have to do here is a define a way to store and retrieve
303 ;;; templates which describe how to walk the 24 special forms and we
306 ;;; Well, its a nice concept, and I have to admit to being naive
307 ;;; enough that I believed it for a while, but not everyone takes
308 ;;; having only 24 special forms as seriously as might be nice. There
309 ;;; are (at least) 3 ways to lose:
311 ;;; 1 - Implementation x implements a Common Lisp special form as
312 ;;; a macro which expands into a special form which:
313 ;;; - Is a common lisp special form (not likely)
314 ;;; - Is not a common lisp special form (on the 3600 IF --> COND).
316 ;;; * We can safe ourselves from this case (second subcase really)
317 ;;; by checking to see whether there is a template defined for
318 ;;; something before we check to see whether we can macroexpand it.
320 ;;; 2 - Implementation x implements a Common Lisp macro as a special form.
322 ;;; * This is a screw, but not so bad, we save ourselves from it by
323 ;;; defining extra templates for the macros which are *likely* to
324 ;;; be implemented as special forms. [Note: As of sbcl-0.6.9, these
325 ;;; extra templates have been deleted, since this is not a problem
326 ;;; in SBCL and we no longer try to make this walker portable
327 ;;; across other possibly-broken CL implementations.]
329 ;;; 3 - Implementation x has a special form which is not on the list of
330 ;;; Common Lisp special forms.
332 ;;; * This is a bad sort of a screw and happens more than I would
333 ;;; like to think, especially in the implementations which provide
334 ;;; more than just Common Lisp (3600, Xerox etc.).
335 ;;; The fix is not terribly satisfactory, but will have to do for
336 ;;; now. There is a hook in get walker-template which can get a
337 ;;; template from the implementation's own walker. That template
338 ;;; has to be converted, and so it may be that the right way to do
339 ;;; this would actually be for that implementation to provide an
340 ;;; interface to its walker which looks like the interface to this
343 (defmacro get-walker-template-internal (x)
344 `(get ,x 'walker-template))
346 (defmacro define-walker-template (name
347 &optional (template '(nil repeat (eval))))
348 `(eval-when (:load-toplevel :execute)
349 (setf (get-walker-template-internal ',name) ',template)))
351 (defun get-walker-template (x)
353 (get-walker-template-internal x))
354 ((and (listp x) (eq (car x) 'lambda))
355 '(lambda repeat (eval)))
357 (error "can't get template for ~S" x))))
359 ;;;; the actual templates
361 ;;; ANSI special forms
362 (define-walker-template block (nil nil repeat (eval)))
363 (define-walker-template catch (nil eval repeat (eval)))
364 (define-walker-template declare walk-unexpected-declare)
365 (define-walker-template eval-when (nil quote repeat (eval)))
366 (define-walker-template flet walk-flet)
367 (define-walker-template function (nil call))
368 (define-walker-template go (nil quote))
369 (define-walker-template if walk-if)
370 (define-walker-template labels walk-labels)
371 (define-walker-template lambda walk-lambda)
372 (define-walker-template let walk-let)
373 (define-walker-template let* walk-let*)
374 (define-walker-template locally walk-locally)
375 (define-walker-template macrolet walk-macrolet)
376 (define-walker-template multiple-value-call (nil eval repeat (eval)))
377 (define-walker-template multiple-value-prog1 (nil return repeat (eval)))
378 (define-walker-template multiple-value-setq walk-multiple-value-setq)
379 (define-walker-template multiple-value-bind walk-multiple-value-bind)
380 (define-walker-template progn (nil repeat (eval)))
381 (define-walker-template progv (nil eval eval repeat (eval)))
382 (define-walker-template quote (nil quote))
383 (define-walker-template return-from (nil quote repeat (return)))
384 (define-walker-template setq walk-setq)
385 (define-walker-template symbol-macrolet walk-symbol-macrolet)
386 (define-walker-template tagbody walk-tagbody)
387 (define-walker-template the (nil quote eval))
388 (define-walker-template throw (nil eval eval))
389 (define-walker-template unwind-protect (nil return repeat (eval)))
391 ;;; SBCL-only special forms
392 (define-walker-template sb-ext:truly-the (nil quote eval))
394 (defvar *walk-form-expand-macros-p* nil)
396 (defun walk-form (form
397 &optional environment
399 (lambda (subform context env)
400 (declare (ignore context env))
402 (walker-environment-bind (new-env environment :walk-function walk-function)
403 (walk-form-internal form :eval new-env)))
405 ;;; WALK-FORM-INTERNAL is the main driving function for the code
406 ;;; walker. It takes a form and the current context and walks the form
407 ;;; calling itself or the appropriate template recursively.
409 ;;; "It is recommended that a program-analyzing-program process a form
410 ;;; that is a list whose car is a symbol as follows:
412 ;;; 1. If the program has particular knowledge about the symbol,
413 ;;; process the form using special-purpose code. All of the
414 ;;; standard special forms should fall into this category.
415 ;;; 2. Otherwise, if MACRO-FUNCTION is true of the symbol apply
416 ;;; either MACROEXPAND or MACROEXPAND-1 and start over.
417 ;;; 3. Otherwise, assume it is a function call. "
418 (defun walk-form-internal (form context env)
419 ;; First apply the walk-function to perform whatever translation
420 ;; the user wants to this form. If the second value returned
421 ;; by walk-function is T then we don't recurse...
423 (multiple-value-bind (newform walk-no-more-p)
424 (funcall (env-walk-function env) form context env)
427 (walk-no-more-p newform)
428 ((not (eq form newform))
429 (walk-form-internal newform context env))
430 ((not (consp newform))
431 (let ((symmac (car (variable-symbol-macro-p newform env))))
433 (let ((newnewform (walk-form-internal (cddr symmac)
436 (if (eq newnewform (cddr symmac))
437 (if *walk-form-expand-macros-p* newnewform newform)
441 (let* ((fn (car newform))
442 (template (get-walker-template fn)))
444 (if (symbolp template)
445 (funcall template newform context env)
446 (walk-template newform template context env))
447 (multiple-value-bind (newnewform macrop)
448 (walker-environment-bind
449 (new-env env :walk-form newform)
450 (macroexpand-1 newform new-env))
453 (let ((newnewnewform (walk-form-internal newnewform
456 (if (eq newnewnewform newnewform)
457 (if *walk-form-expand-macros-p* newnewform newform)
461 (special-operator-p fn))
462 ;; This shouldn't happen, since this walker is now
463 ;; maintained as part of SBCL, so it should know
464 ;; about all the special forms that SBCL knows
466 (error "unexpected special form ~S" fn))
468 ;; Otherwise, walk the form as if it's just a
469 ;; standard function call using a template for
470 ;; standard function call.
472 newnewform '(call repeat (eval)) context env))))))))))))
474 (defun walk-template (form template context env)
477 ((eval function test effect return)
478 (walk-form-internal form :eval env))
481 (walk-form-internal form :set env))
483 (cond ((or (symbolp form)
486 (eq (car form) 'setf)))
488 (t (walk-form-internal form context env)))))
491 (walk-template-handle-repeat form
493 ;; For the case where nothing
494 ;; happens after the repeat
495 ;; optimize away the call to
497 (if (null (cddr template))
499 (nthcdr (- (length form)
507 (if (if (listp (cadr template))
508 (eval (cadr template))
509 (funcall (cadr template) form))
515 (walk-template form (cadr template) context env))
517 (cond ((atom form) form)
520 (car form) (car template) context env)
522 (cdr form) (cdr template) context env))))))))
524 (defun walk-template-handle-repeat (form template stop-form context env)
525 (if (eq form stop-form)
526 (walk-template form (cdr template) context env)
527 (walk-template-handle-repeat-1 form
534 (defun walk-template-handle-repeat-1 (form template repeat-template
535 stop-form context env)
536 (cond ((null form) ())
538 (if (null repeat-template)
539 (walk-template stop-form (cdr template) context env)
540 (error "while handling code walker REPEAT:
541 ~%ran into STOP while still in REPEAT template")))
542 ((null repeat-template)
543 (walk-template-handle-repeat-1
544 form template (car template) stop-form context env))
547 (walk-template (car form) (car repeat-template) context env)
548 (walk-template-handle-repeat-1 (cdr form)
550 (cdr repeat-template)
555 (defun walk-repeat-eval (form env)
558 (walk-form-internal (car form) :eval env)
559 (walk-repeat-eval (cdr form) env))))
561 (defun recons (x car cdr)
562 (if (or (not (eq (car x) car))
563 (not (eq (cdr x) cdr)))
567 (defun relist (x &rest args)
570 (relist-internal x args nil)))
572 (defun relist* (x &rest args)
573 (relist-internal x args t))
575 (defun relist-internal (x args *p)
576 (if (null (cdr args))
579 (recons x (car args) nil))
582 (relist-internal (cdr x) (cdr args) *p))))
586 (defun walk-declarations (body fn env
587 &optional doc-string-p declarations old-body
588 &aux (form (car body)) macrop new-form)
589 (cond ((and (stringp form) ;might be a doc string
590 (cdr body) ;isn't the returned value
591 (null doc-string-p) ;no doc string yet
592 (null declarations)) ;no declarations yet
595 (walk-declarations (cdr body) fn env t)))
596 ((and (listp form) (eq (car form) 'declare))
597 ;; We got ourselves a real live declaration. Record it, look
599 (dolist (declaration (cdr form))
600 (let ((type (car declaration))
601 (name (cadr declaration))
602 (args (cddr declaration)))
603 (if (member type *var-declarations*)
604 (note-declaration `(,type
605 ,(or (var-lexical-p name env) name)
608 (note-declaration declaration env))
609 (push declaration declarations)))
613 (cdr body) fn env doc-string-p declarations)))
616 (null (get-walker-template (car form)))
618 (multiple-value-setq (new-form macrop)
619 (macroexpand-1 form env))
621 ;; This form was a call to a macro. Maybe it expanded
622 ;; into a declare? Recurse to find out.
623 (walk-declarations (recons body new-form (cdr body))
624 fn env doc-string-p declarations
627 ;; Now that we have walked and recorded the declarations,
628 ;; call the function our caller provided to expand the body.
629 ;; We call that function rather than passing the real-body
630 ;; back, because we are RECONSING up the new body.
631 (funcall fn (or old-body body) env))))
633 (defun walk-unexpected-declare (form context env)
634 (declare (ignore context env))
635 (warn "encountered ~S ~_in a place where a DECLARE was not expected"
639 (defun walk-arglist (arglist context env &optional (destructuringp nil)
641 (cond ((null arglist) ())
642 ((symbolp (setq arg (car arglist)))
643 (or (member arg lambda-list-keywords)
644 (note-lexical-binding arg env))
647 (walk-arglist (cdr arglist)
652 lambda-list-keywords))))))
654 (prog1 (recons arglist
656 (walk-arglist arg context env destructuringp)
659 (walk-form-internal (cadr arg) :eval env)
661 (walk-arglist (cdr arglist) context env nil))
662 (if (symbolp (car arg))
663 (note-lexical-binding (car arg) env)
664 (note-lexical-binding (cadar arg) env))
665 (or (null (cddr arg))
666 (not (symbolp (caddr arg)))
667 (note-lexical-binding (caddr arg) env))))
669 (error "can't understand something in the arglist ~S" arglist))))
671 (defun walk-let (form context env)
672 (walk-let/let* form context env nil))
674 (defun walk-let* (form context env)
675 (walk-let/let* form context env t))
677 (defun walk-let/let* (form context old-env sequentialp)
678 (walker-environment-bind (new-env old-env)
679 (let* ((let/let* (car form))
680 (bindings (cadr form))
683 (walk-bindings-1 bindings
689 (walk-declarations body #'walk-repeat-eval new-env)))
691 form let/let* walked-bindings walked-body))))
693 (defun walk-locally (form context env)
694 (declare (ignore context))
695 (let* ((locally (car form))
698 (walk-declarations body #'walk-repeat-eval env)))
700 form locally walked-body)))
702 (defun walk-let-if (form context env)
703 (let ((test (cadr form))
704 (bindings (caddr form))
708 (declare (special ,@(mapcar (lambda (x) (if (listp x) (car x) x))
710 (flet ((.let-if-dummy. () ,@body))
712 (let ,bindings (.let-if-dummy.))
717 (defun walk-multiple-value-setq (form context env)
718 (let ((vars (cadr form)))
719 (if (some (lambda (var)
720 (variable-symbol-macro-p var env))
722 (let* ((temps (mapcar (lambda (var)
723 (declare (ignore var))
726 (sets (mapcar (lambda (var temp) `(setq ,var ,temp))
729 (expanded `(multiple-value-bind ,temps ,(caddr form)
731 (walked (walk-form-internal expanded context env)))
732 (if (eq walked expanded)
735 (walk-template form '(nil (repeat (set)) eval) context env))))
737 (defun walk-multiple-value-bind (form context old-env)
738 (walker-environment-bind (new-env old-env)
739 (let* ((mvb (car form))
740 (bindings (cadr form))
741 (mv-form (walk-template (caddr form) 'eval context old-env))
747 (lambda (real-body real-env)
748 (setq walked-bindings
749 (walk-bindings-1 bindings
754 (walk-repeat-eval real-body real-env))
756 (relist* form mvb walked-bindings mv-form walked-body))))
758 (defun walk-bindings-1 (bindings old-env new-env context sequentialp)
760 (let ((binding (car bindings)))
762 (if (symbolp binding)
764 (note-lexical-binding binding new-env))
765 (prog1 (relist* binding
767 (walk-form-internal (cadr binding)
772 ;; Save cddr for DO/DO*; it is
773 ;; the next value form. Don't
774 ;; walk it now, though.
776 (note-lexical-binding (car binding) new-env)))
777 (walk-bindings-1 (cdr bindings)
783 (defun walk-bindings-2 (bindings walked-bindings context env)
785 (let ((binding (car bindings))
786 (walked-binding (car walked-bindings)))
788 (if (symbolp binding)
792 (cadr walked-binding)
793 (walk-template (cddr binding)
797 (walk-bindings-2 (cdr bindings)
798 (cdr walked-bindings)
802 (defun walk-lambda (form context old-env)
803 (walker-environment-bind (new-env old-env)
804 (let* ((arglist (cadr form))
806 (walked-arglist (walk-arglist arglist context new-env))
808 (walk-declarations body #'walk-repeat-eval new-env)))
814 (defun walk-setq (form context env)
816 (let* ((expanded (let ((rforms nil)
818 (loop (when (null tail) (return (nreverse rforms)))
819 (let ((var (pop tail)) (val (pop tail)))
820 (push `(setq ,var ,val) rforms)))))
821 (walked (walk-repeat-eval expanded env)))
822 (if (eq expanded walked)
825 (let* ((var (cadr form))
827 (symmac (car (variable-symbol-macro-p var env))))
829 (let* ((expanded `(setf ,(cddr symmac) ,val))
830 (walked (walk-form-internal expanded context env)))
831 (if (eq expanded walked)
835 (walk-form-internal var :set env)
836 (walk-form-internal val :eval env))))))
838 (defun walk-symbol-macrolet (form context old-env)
839 (declare (ignore context))
840 (let* ((bindings (cadr form))
842 (walker-environment-bind
845 (append (mapcar (lambda (binding)
847 :macro . ,(cadr binding)))
849 (env-lexical-variables old-env)))
850 (relist* form 'symbol-macrolet bindings
851 (walk-declarations body #'walk-repeat-eval new-env)))))
853 (defun walk-tagbody (form context env)
854 (recons form (car form) (walk-tagbody-1 (cdr form) context env)))
856 (defun walk-tagbody-1 (form context env)
859 (walk-form-internal (car form)
860 (if (symbolp (car form)) 'quote context)
862 (walk-tagbody-1 (cdr form) context env))))
864 (defun walk-macrolet (form context old-env)
865 (walker-environment-bind (macro-env
867 :walk-function (env-walk-function old-env))
868 (labels ((walk-definitions (definitions)
870 (let ((definition (car definitions)))
874 (walk-arglist (cadr definition)
878 (walk-declarations (cddr definition)
881 (walk-definitions (cdr definitions)))))))
882 (with-new-definition-in-environment (new-env old-env form)
885 (walk-definitions (cadr form))
886 (walk-declarations (cddr form)
890 (defun walk-flet (form context old-env)
891 (labels ((walk-definitions (definitions)
892 (if (null definitions)
895 (walk-lambda (car definitions) context old-env)
896 (walk-definitions (cdr definitions))))))
900 (walk-definitions (cadr form))
901 (with-new-definition-in-environment (new-env old-env form)
902 (walk-declarations (cddr form)
906 (defun walk-labels (form context old-env)
907 (with-new-definition-in-environment (new-env old-env form)
908 (labels ((walk-definitions (definitions)
909 (if (null definitions)
912 (walk-lambda (car definitions) context new-env)
913 (walk-definitions (cdr definitions))))))
917 (walk-definitions (cadr form))
918 (walk-declarations (cddr form)
922 (defun walk-if (form context env)
923 (destructuring-bind (if predicate arm1 &optional arm2) form
924 (declare (ignore if)) ; should be 'IF
927 (walk-form-internal predicate context env)
928 (walk-form-internal arm1 context env)
929 (walk-form-internal arm2 context env))))
934 ;;; Here are some examples of the kinds of things you should be able
935 ;;; to do with your implementation of the macroexpansion environment
936 ;;; hacking mechanism.
938 ;;; WITH-LEXICAL-MACROS is kind of like MACROLET, but it only takes
939 ;;; names of the macros and actual macroexpansion functions to use to
940 ;;; macroexpand them. The win about that is that for macros which want
941 ;;; to wrap several MACROLETs around their body, they can do this but
942 ;;; have the macroexpansion functions be compiled. See the WITH-RPUSH
945 ;;; If the implementation had a special way of communicating the
946 ;;; augmented environment back to the evaluator that would be totally
947 ;;; great. It would mean that we could just augment the environment
948 ;;; then pass control back to the implementations own compiler or
949 ;;; interpreter. We wouldn't have to call the actual walker. That
950 ;;; would make this much faster. Since the principal client of this is
951 ;;; defmethod it would make compiling defmethods faster and that would
952 ;;; certainly be a win.
954 (defmacro with-lexical-macros (macros &body body &environment old-env)
955 (with-augmented-environment (new-env old-env :macros macros)
956 (walk-form (cons 'progn body) :environment new-env)))
958 (defun expand-rpush (form env)
959 (declare (ignore env))
960 `(push ,(caddr form) ,(cadr form)))
962 (defmacro with-rpush (&body body)
963 `(with-lexical-macros ,(list (list 'rpush #'expand-rpush)) ,@body))