Evaluation of passed parameters inside macro body - macros

I have a doubt on how parameters passed to the macros are getting evaluated, details below.
This macro is defined
(defmacro test-macro (xlist)
`(* ,#xlist))
and there is this global variable (defvar *test-list* '(1 100 2 200)).
When *test-list* is passed to this macro (test-macro *test-list*) , this error is returned -
value *TEST-LIST* is not of the expected type LIST.
[Condition of type TYPE-ERROR]
But if the function is modified to this, list is returned
(defmacro test-macro (xlist)
`(,#xlist)) ;; removed the * operator
(test-macro *test-list*) will return (1 100 2 200).
So my doubt is why ,#xlist is not getting evaluated in the first case, i.e when the * operator is applied. Any help is highly appreciated.

When debugging macros, The Right Way is to use macroexpand, not evaluate the macro forms. E.g., in your case:
(defmacro test-macro1 (xlist) `(* ,#xlist))
(macroexpand '(test-macro1 foo))
==> (* . FOO)
(defmacro test-macro2 (xlist) `(,#xlist))
(macroexpand '(test-macro2 foo))
==> FOO
neither is probably what you want.

The confusion is that the macro is a pre-processor: it has no built-in mechanism to know of runtime values. So when you use the term:
(test-macro test-list)
all that the macro sees is the identifier test-list: it does not know up-front that the runtime value is a list, only that the source program has used this variable identifier.
A macro is a source-to-source rewriter: it doesn't know about the dynamics of your program. A smarter compiler might be able to see that test-list is a constant and do an inlining, but the macro expander isn't that clever.
What you can do is probably something like this:
(defmacro test-macro (xlist)
(cond
(;; If we see test-macro is being used with a quoted list of things
;; then we can rewrite that statically.
(and (pair? xlist)
(eq? (car xlist) 'quote)
(list? (cadr xlist)))
`(list 'case-1 (* ,#(cadr xlist))))
(;; Also, if we see test-macro is being used with "(list ...)"
;; then we can rewrite that statically.
(and (pair? xlist)
(eq? (car xlist) 'list))
`(list 'case-2 (* ,#(cdr xlist))))
(else
;; Otherwise, do the most generic thing:
`(list 'case-3 (apply * ,xlist)))))
;; This hits the first case:
(test-macro '(3 4 5))
;; ... the second case:
(test-macro (list 5 6 7))
;; ... and the third case:
(defvar test-list '(1 100 2 200))
(test-macro test-list)
With regards to your second version: the macro:
(defmacro test-macro (xlist)
`(,#xlist))
is equivalent to:
(defmacro test-macro (xlist)
xlist)
so that's why you're not getting the error that you received in the first version.

Related

Rewrite loop as a mapcar

Looking at Practical Common Lisp, we're looking at a simple automated unit test framework. We're trying to write a macro to be used as such:
(check (= (+ 1 2) 3) (= (- 1 4) 9))
This should expand to something using a previously defined function report-result. The suggested implementation is:
(defmacro check (&body forms)
`(progn
,#(loop for f in forms collect `(report-result ,f ',f))))
However, that expansion seems rather procedural to me. I wanted to replace the loop with a mapcar to expand to something like this:
(mapcar #'(lambda (form) (report-result form 'form)) (list form-1 ... form-n))
However, I'm clearly lacking the macro-writing skills to do so. Can someone come up with one such macro?
In case it's relevant, this is the definition of report-result:
(defun report-result (result form)
(format t "~:[FAIL~;pass~] ... ~a~%" result form))
It's indeed fairly simple: you just place the collect expression into the body of your mapcar:
(defmacro check (&body forms)
`(progn
,#(mapcar #'(lambda (form)
`(report-result ,form ',form))
forms)))
You don't really need to know anything about the "macro-y" stuff that's going on, in order to do the replacement you want, which is simply replacing a loop with some other equivalent expression: it will work just as well in a macro context as it would outside.
If you want to expand to a mapcar you can, but there's no real reason to do so, since the list's size is known at compile time. Here's what that would look like:
(defmacro check (&body forms)
`(let ((results (list ,#(mapcar #'(lambda (form)
`(list ,form ',form))
forms))))
(mapcar #'(lambda (result)
(report-result (car result) (cadr result)))
results)))
Which expands like so
> (macroexpand-1 '(check (+ 1 2) (* 2 3)))
(let ((results (list (list (+ 1 2) '(+ 1 2))
(list (* 2 3) '(* 2 3)))))
(mapcar #'(lambda (result) (report-result (car result) (cadr result)))
results))
Which as you can see is rather awkward: the macro already has the forms like (+ 1 2) available to it, but in order to preserve them to runtime for the mapcar lambda to see, you have to emit the input form twice. And you have to produce the whole list to map over, rather than just producing a list that's "finished" to begin with. Additionally, this produces a list as output, and requires having all the inputs and outputs in memory at once: the original macro with progn produced the inputs and outputs one at a time, and discarded them when finished.

macro to feed a calculated binding list into a 'let'?

I'm trying different binding models for macro lambda lists.
Edit: in fact the lambda list for my test macros is always (&rest ...). Which means that I'm 'destructuring' the argument list and not the lambda list. I try to get a solution that works for combining optional with key arguments or rest/body with key arguments - both combinations don't work in the Common Lisp standard implementation.
So I have different functions giving me a list of bindings having the same syntax as used by 'let'.
E.g:
(build-bindings ...) => ((first 1) middle (last "three"))
Now I thought to use a simple macro inside my test macros feeding such a list to 'let'.
This is trivial if I have a literal list:
(defmacro let-list (_list &rest _body)
`(let ,_list ,#_body))
(let-list ((a 236)) a) => 236
But that's the same as a plain 'let'.
What I'd like to have is the same thing with a generated list.
So e.g.
(let-list (build-bindings ...)
(format t "first: ~s~%" first)
last)
with (build-bindings ...), evaluated in the same lexical scope as the call (let-list ...), returning
((first 1) middle (last "three"))
the expansion of the macro should be
(let
((first 1) middle (last "three"))
(format t "first: ~s~%" first)
last)
and should print 1 and return "three".
Any idea how to accomplish that?
Edit (to make the question more general):
If I have a list of (symbol value) pairs, i.e. same syntax that let requires for it's list of bindings, e.g. ((one 1) (two 'two) (three "three")), is there any way to write a macro that creates lexical bindings of the symbols with the supplied values for it's &rest/&body parameter?
This is seems to be a possible solution which Joshua pointed me to:
(let ((list_ '((x 23) (y 6) z)))
(let
((symbols_(loop for item_ in list_
collect (if (listp item_) (car item_) item_)))
(values_ (loop for item_ in list_
collect (if (listp item_) (cadr item_) nil))))
(progv symbols_ values_
(format t "x ~s, y ~s, z ~s~%" x y z))))
evaluates to:
;Compiler warnings :
; In an anonymous lambda form: Undeclared free variable X
; In an anonymous lambda form: Undeclared free variable Y
; In an anonymous lambda form: Undeclared free variable Z
x 23, y 6, z NIL
I could also easily rearrange my build-bindings functions to return the two lists needed.
One problem is, that the compiler spits warnings if the variables have never been declared special.
And the other problem that, if the dynamically bound variables are also used in a surrounding lexical binding, they a shadowed by the lexical binding - again if they have never been declared special:
(let ((x 47) (y 11) (z 0))
(let ((list_ '((x 23) (y 6) z)))
(let
((symbols_(loop for item_ in list_
collect (if (listp item_) (car item_) item_)))
(values_ (loop for item_ in list_
collect (if (listp item_) (cadr item_) nil))))
(progv symbols_ values_
(format t "x ~s, y ~s, z ~s~%" x y z)))))
evaluates to:
x 47, y 11, z 0
A better way could be:
(let ((x 47) (y 11) (z 0))
(locally
(declare (special x y))
(let ((list_ '((x 23) (y 6) z)))
(let
((symbols_(loop for item_ in list_
collect (if (listp item_) (car item_) item_)))
(values_ (loop for item_ in list_
collect (if (listp item_) (cadr item_) nil))))
(progv symbols_ values_
(format t "x ~s, y ~s, z ~s~%" x y z))))))
evaluates to:
;Compiler warnings about unused lexical variables skipped
x 23, y 6, z NIL
I can't see at the moment whether there are other problems with the dynamic progv bindings.
But the whole enchilada of a progv wrapped in locally with all the symbols declared as special cries for a macro again - which is again not possible due to same reasons let-list doesn't work :(
The possiblilty would be a kind of macro-lambda-list destructuring-hook which I'm not aware of.
I have to look into the implementation of destructuring-bind since that macro does kind of what I'd like to do. Perhaps that will enlight me ;)
So a first (incorrect) attempt would look something like this:
(defun build-bindings ()
'((first 1) middle (last "three")))
(defmacro let-list (bindings &body body)
`(let ,bindings
,#body))
Then you could try doing something like:
(let-list (build-bindings)
(print first))
That won't work, of course, because the macro expansion leaves the form (build-bindings) in the resulting let, in a position where it won't be evaluated:
CL-USER> (pprint (macroexpand-1 '(let-list (build-bindings)
(print first))))
(LET (BUILD-BINDINGS)
(PRINT FIRST))
Evaluation during Macroexpansion time
The issue is that you want the result of build-bindings at macroexpansion time, and that's before the code as a whole is run. Now, in this example, build-bindings can be run at macroexpansion time, because it's not doing anything with any arguments (remember I asked in a comment what the arguments are?). That means that you could actually eval it in the macroexpansion:
(defmacro let-list (bindings &body body)
`(let ,(eval bindings)
,#body))
CL-USER> (pprint (macroexpand-1 '(let-list (build-bindings)
(print first))))
(LET ((FIRST 1) MIDDLE (LAST "three"))
(PRINT FIRST))
Now that will work, insofar as it will bind first, middle, and last to 1, nil, and "three", respectively. However, if build-bindings actually needed some arguments that weren't available at macroexpansion time, you'd be out of luck. First, it can take arguments that are available at macroexpansion time (e.g., constants):
(defun build-bindings (a b &rest cs)
`((first ',a) (middle ',b) (last ',cs)))
CL-USER> (pprint (macroexpand-1 '(let-list (build-bindings 1 2 3 4 5)
(print first))))
(LET ((FIRST '1) (MIDDLE '2) (LAST '(3 4 5)))
(PRINT FIRST))
You could also have some of the variables appear in there:
(defun build-bindings (x ex y why)
`((,x ,ex) (,y ,why)))
CL-USER> (pprint (macroexpand-1 '(let-list (build-bindings 'a 'ay 'b 'bee)
(print first))))
(LET ((A AY) (B BEE))
(PRINT FIRST))
What you can't do, though, is have the variable names be determined from values that don't exist until runtime. E.g., you can't do something like:
(let ((var1 'a)
(var2 'b))
(let-list (build-bindings var1 'ay var2 'bee)
(print first))
because (let-list (build-bindings …) …) is macroexpanded before any of this code is actually executed. That means that you'd be trying to evaluate (build-bindings var1 'ay var2 'bee) when var1 and var2 aren't bound to any values.
Common Lisp does all its macroexpansion first, and then evaluates code. That means that values that aren't available until runtime are not available at macroexpansion time.
Compilation (and Macroexpansion) at Runtime
Now, even though I said that Common Lisp does all its macroexpansion first, and then evaluates code, the code above actually uses eval at macroexpansion to get some extra evaluation earlier. We can do things in the other direction too; we can use compile at runtime. That means that we can generate a lambda function and compile it based on code (e.g., variable names) provided at runtime. We can actually do this without using a macro:
(defun %dynamic-lambda (bindings body)
(flet ((to-list (x) (if (listp x) x (list x))))
(let* ((bindings (mapcar #'to-list bindings))
(vars (mapcar #'first bindings))
(vals (mapcar #'second bindings)))
(apply (compile nil `(lambda ,vars ,#body)) vals))))
CL-USER> (%dynamic-lambda '((first 1) middle (last "three"))
'((list first middle last)))
;=> (1 NIL "three")
This compiles a lambda expression that is created at runtime from a body and a list of bindings. It's not hard to write a macro that takes some fo the quoting hassle out of the picture:
(defmacro let-list (bindings &body body)
`(%dynamic-lambda ,bindings ',body))
CL-USER> (let-list '((first 1) middle (last "three"))
(list first middle last))
;=> (1 NIL "three")
CL-USER> (macroexpand-1 '(let-list (build-bindings)
(list first middle last)))
;=> (%DYNAMIC-LAMBDA (BUILD-BINDINGS) '((LIST FIRST MIDDLE LAST)))
CL-USER> (flet ((build-bindings ()
'((first 1) middle (last "three"))))
(let-list (build-bindings)
(list first middle last)))
;=> (1 NIL "three")
This gives you genuine lexical variables from a binding list created at runtime. Of course, because the compilation is happening at runtime, you lose access to the lexical environment. That means that the body that you're compiling into a function cannot access the "surrounding" lexical scope. E.g.:
CL-USER> (let ((x 3))
(let-list '((y 4))
(list x y)))
; Evaluation aborted on #<UNBOUND-VARIABLE X {1005B6C2B3}>.
Using PROGV and special variables
If you don't need lexical variables, but can use special (i.e., dynamically scoped) variables instead, you can establish bindings at runtime using progv. That would look something like:
(progv '(a b c) '(1 2 3)
(list c b a))
;;=> (3 2 1)
You'll probably get some warnings with that if run it, because when the form is compiled, there's no way to know that a, b, and c are supposed to be special variables. You can use locally to add some special declarations, though:
(progv '(a b c) '(1 2 3)
(locally
(declare (special a b c))
(list c b a)))
;;=> (3 2 1)
Of course, if you're doing this, then you have to know the variables in advance which is exactly what you were trying to avoid in the first place. However, if you're willing to know the names of the variables in advance (and your comments seem like you might be okay with that), then you can actually use lexical variables.
Lexical variables with values computed at run time
If you're willing to state what the variables will be, but still want to compute their values dynamically at run time, you can do that relatively easily. First, lets write the direct version (with no macro):
;; Declare three lexical variables, a, b, and c.
(let (a b c)
;; Iterate through a list of bindings (as for LET)
;; and based on the name in the binding, assign the
;; corresponding value to the lexical variable that
;; is identified by the same symbol in the source:
(dolist (binding '((c 3) (a 1) b))
(destructuring-bind (var &optional value)
(if (listp binding) binding (list binding))
(ecase var
(a (setf a value))
(b (setf b value))
(c (setf c value)))))
;; Do something with the lexical variables:
(list a b c))
;;=> (1 NIL 3)
Now, it's not too hard to write a macrofied version of this. This version isn't perfect, (e.g., there could be hygiene issues with names, and declarations in the body won't work (because the body is being spliced in after some stuff). It's a start, though:
(defmacro computed-let (variables bindings &body body)
(let ((assign (gensym (string '#:assign-))))
`(let ,variables
(flet ((,assign (binding)
(destructuring-bind (variable &optional value)
(if (listp binding) binding (list binding))
(ecase variable
,#(mapcar (lambda (variable)
`(,variable (setf ,variable value)))
variables)))))
(map nil #',assign ,bindings))
,#body)))
(computed-let (a b c) '((a 1) b (c 3))
(list a b c))
;;=> (1 NIL 3)
One way of making this cleaner would be to avoid the assignment altogether, and the computed values to provide the values for the binding directly:
(defmacro computed-let (variables bindings &body body)
(let ((values (gensym (string '#:values-)))
(variable (gensym (string '#:variable-))))
`(apply #'(lambda ,variables ,#body)
(let ((,values (mapcar #'to-list ,bindings)))
(mapcar (lambda (,variable)
(second (find ,variable ,values :key 'first)))
',variables)))))
This version creates a lambda function where the arguments are the specified variables and the body is the provided body (so the declarations in the body are in an appropriate place), and then applies it to a list of values extracted from the result of the computed bindings.
Using LAMBDA or DESTRUCTURING-BIND
since I'm doing some "destructuring" of the arguments (in a bit a different way), I know which arguments must be present or have which
default values in case of missing optional and key arguments. So in
the first step I get a list of values and a flag whether an optional
or key argument was present or defaulted. In the second step I would
like to bind those values and/or present/default flag to local
variables to do some work with them
This is actually starting to sound like you can do what you need to by using a lambda function or destructuring-bind with keyword arguments. First, note that you can use any symbol as a keyword argument indicator. E.g.:
(apply (lambda (&key
((b bee) 'default-bee b?)
((c see) 'default-see c?))
(list bee b? see c?))
'(b 42))
;;=> (42 T DEFAULT-SEE NIL)
(destructuring-bind (&key ((b bee) 'default-bee b?)
((c see) 'default-see c?))
'(b 42)
(list bee b? see c?))
;;=> (42 T DEFAULT-SEE NIL)
So, if you just make your function return bindings as a list of keyword arguments, then in the destructuring or function application you can automatically bind corresponding variables, assign default values, and check whether non-default values were provided.
Acting a bit indirectly:
a solution that works for combining optional with key arguments or
rest/body with key arguments
Have you considered the not-entirely-uncommon paradigm of using a sub-list for the keywords?
e.g.
(defmacro something (&key (first 1) second) &body body) ... )
or, a practical use from Alexandria:
(defmacro with-output-to-file ((stream-name file-name
&rest args
&key (direction nil direction-p)
&allow-other-keys)
&body body)

Function name and dynamic binding in Common Lisp

I'm reading Peter Norvig's Paradigms of AI. In chapter 6.2, the author uses code like below (not the original code, I picked out the troubling part):
Code Snippet:
(progv '(op arg) '(1+ 1)
(eval '(op arg)))
As the author's original intent, this code should return 2, but in sbcl 1.1.1, the interpreter is apparently not looking up op in the environment, throwing out op: undefined function.
Is this implementation specific? Since the code must have been tested on some other lisp.
p.s Original code
You probably mean
(progv '(op arg) '(1+ 1)
(eval '(funcall op arg)))
Edit(2013-08-21):
PAIP was written in pre-ANSI-Common-Lisp era, so it's possible the code
there contains a few noncompliances wrt the standard. We can make
the examples work with the following revision:
(defun match-if (pattern input bindings)
"Test an arbitrary expression involving variables.
The pattern looks like ((?if code) . rest)."
(and (eval (reduce (lambda (code binding)
(destructuring-bind (var . val) binding
(subst val var code)))
bindings :initial-value (second (first pattern))))
(pat-match (rest pattern) input bindings)))
;; CL-USER> (pat-match '(?x ?op ?y is ?z (?if (eql (?op ?x ?y) ?z))) '(3 + 4 is 7))
;; ((?Z . 7) (?Y . 4) (?OP . +) (?X . 3) (T . T))
;; CL-USER> (pat-match '(?x ?op ?y (?if (?op ?x ?y))) '(3 > 4))
;; NIL
Elements in first positions are not looked up as values, but as functions and there is no concept of dynamic binding in the function namespace.
I'd say after a quick look that the original code was designed to evaluate in a context like
(progv '(x y) '(12 34)
(eval '(> (+ x y) 99)))
i.e. evaluating a formula providing substitution for variables, not for function names.
The other answers so far are right, in that the actual form being evaluated is not the variables being bound by progv (simply (op arg)), but none have mentioned what is being evaluated. In fact, the comments in the code you linked to provide a (very) short explanation (this is the only code in that file that uses progv):
(defun match-if (pattern input bindings)
"Test an arbitrary expression involving variables.
The pattern looks like ((?if code) . rest)."
;; *** fix, rjf 10/1/92 (used to eval binding values)
(and (progv (mapcar #'car bindings)
(mapcar #'cdr bindings)
(eval (second (first pattern))))
(pat-match (rest pattern) input bindings)))
The idea is that a call to match-if gets called like
(match-if '((?if code) . rest) input ((v1 val1) (v2 val2) ...))
and eval is called with (second (first pattern)), which the value of code. However, eval is called within the progv that binds v1, v2, &c., to the corresponding val1, val2, &c., so that if any of those variables appear free in code, then they are bound when code is evaluated.
Problem
The problem that I see here is that, by the code we can't tell if the value is to be saved as the variable's symbol-value or symbol-function. Thus when you put a + as a value to some corresponding variable, say v, then it'll always be saved as the symbol-value of var, not it's symbol-function.
Therefore when you'll try to use it as, say (v 1 2) , it won't work. Because there is no function named v in the functions' namespace(see this).
So, what to do?
A probable solution can be explicit checking for the value that is to be bound to a variable. If the value is a function, then it should be bound to the variable's function value. This checking can be done via fboundp.
So, we can make a macro functioner and a modified version of match-if. functioner checks if the value is a function, and sets it aptly. match-if does the dynamic local bindings, and allows other code in the scope of the bound variables.
(defmacro functioner (var val)
`(if (and (symbolp ',val)
(fboundp ',val))
(setf (symbol-function ',var) #',val)
(setf ,var ,val)))
(defun match-if (pattern input bindings)
(eval `(and (let ,(mapcar #'(lambda (x) (list (car x))) bindings)
(declare (special ,# (mapcar #'car bindings)))
(loop for i in ',bindings
do (eval `(functioner ,(first i) ,(rest i))))
(eval (second (first ',pattern))))
(pat-match (rest ',pattern) ',input ',bindings))))

scheme macro produces unexpected result

Does someone know why the following produces the expected result - (2 4 6)
(defmacro mult2 (lst)
(define (itter x)
(list '* 2 x))
`(list ,#(map itter lst)))
(mult2 (1 2 3))
while I expected that this one would (with the list identifier)
(defmacro mult2 (lst)
(define (itter x)
(list '* 2 x))
`(list ,#(map itter lst)))
(mult2 '(1 2 3))
Macro "arguments" are not evaluated. So, when you pass in '(1 2 3), i.e., (quote (1 2 3)), that is exactly what the macro sees.
P.S. You are much better off using hygienic macros in Scheme. Here's an example using syntax-case:
(define-syntax mult2
(lambda (stx)
(define (double x)
#`(* 2 #,x))
(syntax-case stx ()
((_ lst)
#`(list #,#(map double (syntax-e #'lst)))))))
(That's still not how such a macro is idiomatically written, but I tried to mirror your version as closely as possible.)
That's because the '(1 2 3) is expanded by the reader into (quote (1 2 3)). Since you only destructure one list in your macro, it won't work as expected.
Some general advice: if you're working in Racket you probably want to avoid using defmacro. That is definitely not the idiomatic way to write macros. Take a look at syntax-rules and, if you want to define more complicated macros, syntax-parse. Eli also wrote an article explaining syntax-case for people used to defmacro.

Common Lisp Backquote/Backtick: How to Use?

I am having trouble with Lisp's backquote read macro. Whenever I try to write a macro that seems to require the use of embedded backquotes (e.g., ``(w ,x ,,y) from Paul Graham's ANSI Common Lisp, page 399), I cannot figure out how to write my code in a way that compiles. Typically, my code receives a whole chain of errors preceded with "Comma not inside a backquote." Can someone provide some guidelines for how I can write code that will evaluate properly?
As an example, I currently need a macro which takes a form that describes a rule in the form of '(function-name column-index value) and generates a predicate lambda body to determine whether the element indexed by column-index for a particular row satisfies the rule. If I called this macro with the rule '(< 1 2), I would want a lambda body that looks like the following to be generated:
(lambda (row)
(< (svref row 1) 2))
The best stab I can make at this is as follows:
(defmacro row-satisfies-rule (rule)
(let ((x (gensym)))
`(let ((,x ,rule))
(lambda (row)
(`,(car ,x) (svref row `,(cadr ,x)) `,(caddr ,x))))))
Upon evaluation, SBCL spews the following error report:
; in: ROW-SATISFIES-RULE '(< 1 2)
; ((CAR #:G1121) (SVREF ROW (CADR #:G1121)) (CADDR #:G1121))
;
; caught ERROR:
; illegal function call
; (LAMBDA (ROW) ((CAR #:G1121) (SVREF ROW (CADR #:G1121)) (CADDR #:G1121)))
; ==>
; #'(LAMBDA (ROW) ((CAR #:G1121) (SVREF ROW (CADR #:G1121)) (CADDR #:G1121)))
;
; caught STYLE-WARNING:
; The variable ROW is defined but never used.
; (LET ((#:G1121 '(< 1 2)))
; (LAMBDA (ROW) ((CAR #:G1121) (SVREF ROW (CADR #:G1121)) (CADDR #:G1121))))
;
; caught STYLE-WARNING:
; The variable #:G1121 is defined but never used.
;
; compilation unit finished
; caught 1 ERROR condition
; caught 2 STYLE-WARNING conditions
#<FUNCTION (LAMBDA (ROW)) {2497F245}>
How can I write macros to generate the code I need, and in particular, how do I implement row-satisfies-rule?
Using the ideas from Ivijay and discipulus, I have modified the macro so that it compiles and works, even allowing forms to be passed as the arguments. It runs a bit differently from my originally planned macro since I determined that including row as an argument made for smoother code. However, it is ugly as sin. Does anyone know how to clean it up so it performs the same without the call to eval?
(defmacro row-satisfies-rule-p (row rule)
(let ((x (gensym))
(y (gensym)))
`(let ((,x ,row)
(,y ,rule))
(destructuring-bind (a b c) ,y
(eval `(,a (svref ,,x ,b) ,c))))))
Also, an explanation of clean, Lispy ways to get macros to generate code to properly evaluate the arguments at runtime would be greatly appreciated.
First of all, Lisp macros have "destructuring" argument lists. This is a nice feature that means instead of having an argument list (rule) and then taking it apart with (car rule) (cadr rule) (caddr rule), you can simply make the argument list ((function-name column-index value)). That way the macro expects a list of three elements as an argument, and each element of the list is then bound to the corresponding symbol in the arguemnt list. You can use this or not, but it's usually more convenient.
Next, `, doesn't actually do anything, because the backquote tells Lisp not to evaluate the following expression and the comma tells it to evaluate it after all. I think you meant just ,(car x), which evaluates (car x). This isn't a problem anyway if you use destructuring arguments.
And since you're not introducing any new variables in the macro expansion, I don't think (gensym) is necessary in this case.
So we can rewrite the macro like this:
(defmacro row-satisfies-rule ((function-name column-index value))
`(lambda (row)
(,function-name (svref row ,column-index) ,value)))
Which expands just how you wanted:
(macroexpand-1 '(row-satisfies-rule (< 1 2)))
=> (LAMBDA (ROW) (< (SVREF ROW 1) 2))
Hope this helps!
If you need the argument to be evaluated to get the rule set, then here's a nice way to do it:
(defmacro row-satisfies-rule (rule)
(destructuring-bind (function-name column-index value) (eval rule)
`(lambda (row)
(,function-name (svref row ,column-index) ,value))))
Here's an example:
(let ((rules '((< 1 2) (> 3 4))))
(macroexpand-1 '(row-satisfies-rule (car rules))))
=> (LAMBDA (ROW) (< (SVREF ROW 1) 2))
just like before.
If you want to include row in the macro and have it give you your answer straightaway instead of making a function to do that, try this:
(defmacro row-satisfies-rule-p (row rule)
(destructuring-bind (function-name column-index value) rule
`(,function-name (svref ,row ,column-index) ,value)))
Or if you need to evaluate the rule argument (e.g. passing '(< 1 2) or (car rules) instead of (< 1 2)) then just use (destructuring-bind (function-name column-index value) (eval rule)
Actually, a function seems more appropriate than a macro for what you're trying to do. Simply
(defun row-satisfies-rule-p (row rule)
(destructuring-bind (function-name column-index value) rule
(funcall function-name (svref row column-index) value)))
works the same way as the macro and is much neater, without all the backquoting mess to worry about.
In general, it's bad Lisp style to use macros for things that can be accomplished by functions.
One thing to understand is that the backquote feature is completely unrelated to macros. It can be used for list creation. Since source code usually consists of lists, it may be handy in macros.
CL-USER 4 > `((+ 1 2) ,(+ 2 3))
((+ 1 2) 5)
The backquote introduces a quoted list. The comma does the unquote: the expression after the comma is evaluated and the result inserted. The comma belongs to the backquote: the comma is only valid inside a backquote expression.
Note also that this is strictly a feature of the Lisp reader.
Above is basically similar to:
CL-USER 5 > (list '(+ 1 2) (+ 2 3))
((+ 1 2) 5)
This creates a new list with the first expression (not evaluated, because quoted) and the result of the second expression.
Why does Lisp provide backquote notation?
Because it provides a simple template mechanism when one wants to create lists where most of the elements are not evaluated, but a few are. Additionally the backquoted list looks similar to the result list.
you don't need nested backquotes to solve this problem. Also, when it's a macro, you don't have to quote your arguments. So (row-satisfies-rule (< 1 2)) is lispier than (row-satisfies-rule '(< 1 2)).
(defmacro row-satisfies-rule (rule)
(destructuring-bind (function-name column-index value) rule
`(lambda (row)
(,function-name (svref row ,column-index) ,value))))
will solve the problem for all calls in the first form. Solving the problem when in the second form is left as an exercise.