How can I modify the #+ and #- readtable macros in Lisp? - macros

Short version:
I want to change the #+ and #- reader macros to apply to all immediately subsequent tokens starting with ##, in addition to the following token. Therefore, the following code...
#+somefeature
##someattribute1
##someattribute2
(defun ...)
...would, in the absence of somefeature, result in no code.
Long version:
I have written my own readtable-macros which apply transformations to subsequent code. For example:
##traced
(defun ...)
This yields a function that writes its arguments and return values to a file, for debugging.
This fails, however, when used in conjunction with the #+ reader macro:
#+somefeature
##traced
(defun ...)
In the absence of somefeature, the function continues to be defined, albeit without the ##traced modification. This is obviously not the desired outcome.
One possible solution would be to use progn, as follows:
#+somefeature
(progn
##traced
(defun ...))
But that's kind of ugly.
I would like to modify the #+ and #- reader macros, such that they may consume more than one token. Something like this:
(defun conditional-syntax-reader (stream subchar arg)
; If the conditional fails, consume subsequent tokens while they
; start with ##, then consume the next token.
)
(setf *readtable* (copy-readtable))
(set-dispatch-macro-character #\# #\+ #'conditional-syntax-reader)
(set-dispatch-macro-character #\# #\- #'conditional-syntax-reader)
The problem is, I don't know how to "delegate" to the original reader macros; and I don't understand enough about how they were implemented to re-implement them myself in their entirety.
A naive approach would be:
(defun consume-tokens-recursively (stream)
(let ((token (read stream t nil t)))
(when (string= "##" (subseq (symbol-string token) 0 2))
(consume-tokens-recursively stream)))) ; recurse
(defun conditional-syntax-reader (stream subchar arg)
(unless (member (read stream t nil t) *features*)
(consume-tokens-recursively stream)))
However, I'm given to believe that this wouldn't be sufficient:
The #+ syntax operates by first reading the feature specification and then skipping over the form if the feature is false. This skipping of a form is a bit tricky because of the possibility of user-defined macro characters and side effects caused by the #. and #, constructions. It is accomplished by binding the variable read-suppress to a non-nil value and then calling the read function.
This seems to imply that I can just let ((*read-suppress* t)) when using read to solve the issue. Is that right?
EDIT 1
Upon further analysis, it seems the problem is caused by not knowing how many tokens to consume. Consider the following attributes:
##export expects one argument: the (defun ...) to export.
##traced expects two arguments: the debug level and the (defun ...) to trace.
Example:
#+somefeature
##export
##traced 3
(defun ...)
It turns out that #+ and #- are capable of suppressing all these tokens; but there is a huge problem!
When under a suppressing #+ or #-, (read) returns NIL!
Example:
(defun annotation-syntax-reader (stream subchar arg)
(case (read stream t nil t)
('export
(let ((defun-form (read stream t nil t)))))
; do something
('traced
(let* ((debug-level (read stream t nil t))
(defun-form (read stream t nil t)))))))
; do something
(setf *readtable* (copy-readtable))
(set-dispatch-macro-character #\# #\# #'annotation-syntax-reader)
#+(or) ##traced 3 (defun ...)
The ##traced token is being suppressed by the #+. In this situation, all the (read) calls in (annotation-syntax-reader) consume real tokens but return NIL!
Therefore, the traced token is consumed, but the case fails. No additional tokens are thus consumed; and control leaves the scope of the #+.
The (defun ...) clause is executed as normal, and the function comes into being. Clearly not the desired outcome.

The standard readtable
Changing the macros for #+ and #- is a bit excessive solution I think, but in any case remember to not actually change the standard readtable (as you did, but its important to repeat in the answer)
The consequences are undefined if an attempt is made to modify the standard readtable. To achieve the effect of altering or extending standard syntax, a copy of the standard readtable can be created; see the function copy-readtable.
§2.1.1.2 The Standard Readtable
Now, maybe I'm missing something (please give us a hint about how your reader macro is defined if so), but I think it is possible to avoid that and write your custom macros in a way that works for your use case.
Reader macro
Let's define a simple macro as follows:
CL-USER> (defun my-reader (stream char)
(declare (ignore char))
(let ((name (read stream)
(form (read stream))
(unless *read-suppress*
`(with-decoration ,name ,form)))
MY-READER
[NB: This was edited to take into account *read-suppress*: the code always read two forms, but returns nil in case it is being ignored. In the comments you say that you may need to read an indefinite number of forms based on the name of the decoration, but with *read-suppress* the recursive calls to read return nil for symbols, so you don't know which decoration is being applied. In that case it might be better to wrap some arguments in a literal list, or parse the stream manually (read-char, etc.). Also, since you are using a dispatching macro, maybe you can add a numerical argument if you want the decoration to be applied to more than one form (#2#inline), but that could be a bad idea when later the decorated code is being modified.]
Here the reader does a minimal job, namely build a form that is intended to be macroexpanded later. I don't even need to define with-decoration for now, as I'm interested in the read step. The intent is to read the next token (presumably a symbol that indicates what decoration is being applied, and a form to decorate).
I'm binding this macro to a unused character:
CL-USER> (set-macro-character #\§ 'my-reader)
T
Here when I test the macro it wraps the following form:
CL-USER> (read-from-string "§test (defun)")
(WITH-DECORATION TEST (DEFUN))
13 (4 bits, #xD, #o15, #b1101)
And here it works with a preceding QUOTE too, the apostrophe reader grabs the next form, which recursively reads two forms:
CL-USER> '§test (defun)
(WITH-DECORATION TEST (DEFUN))
Likewise, a conditional reader macro will ignore all the next lines:
CL-USER> #+(or) t
; No values
CL-USER> #+(or) §test (defun)
; No values
CL-USER> #+(or) §one §two §three (defun)
; No values
Decoration macro
If you use this syntax, you'll have nested decorated forms:
CL-USER> '§one §two (defun test ())
(WITH-DECORATION ONE (WITH-DECORATION TWO (DEFUN TEST ())))
With respect to defun in toplevel positions, you can arrange for your macros to unwrap the nesting (not completely tested, there might be bugs):
(defun unwrap-decorations (form stack)
(etypecase form
(cons (destructuring-bind (head . tail) form
(case head
(with-decoration (destructuring-bind (token form) tail
(unwrap-decorations form (cons token stack))))
(t `(with-decorations ,(reverse stack) ,form)))))))
CL-USER> (unwrap-decorations ** nil)
(WITH-DECORATIONS (ONE TWO) (DEFUN TEST ()))
And in turn, with-decorations might know about DEFUN forms and how to annotate them as necessary.
For the moment, our original macro is only the following (it needs more error checking):
(defmacro with-decoration (&whole whole &rest args)
(unwrap-decorations whole nil))
For the sake of our example, let's define a generic annotation mechanism:
CL-USER> (defgeneric expand-decoration (type name rest))
#<STANDARD-GENERIC-FUNCTION COMMON-LISP-USER::EXPAND-DECORATION (0)>
It is used in with-decorations to dispatch on an appropriate expander for each decoration. Keep in mind that all the efforts here are to keep defun in a top-level positions (under a progn), a recursive annotation would let evaluation happens (in the case of defun, it would result in the name of the function being defined), and the annotation could be done on the result.
The main macro is then here, with a kind of fold (reduce) mechanism where the forms are decorated using the resulting expansion so far. This allows for expanders to place code before or after the main form (or do other fancy things):
(defmacro with-decorations ((&rest decorations) form)
(etypecase form
(cons (destructuring-bind (head . tail) form
(ecase head
(defun (destructuring-bind (name args . body) tail
`(progn
,#(loop
for b = `((defun ,name ,args ,#body)) then forms
for d in decorations
for forms = (expand-decoration d name b)
finally (return forms))))))))))
(nb. here above we only care about defun but the loop should probably be done outside of the dispatching thing, along with a way to indicate to expander methods that a function is being expanded; well, it could be better)
Say, for example, you want to declare a function as inline, then the declaration must happen before (so that the compiler can know the source code must be kept):
(defmethod expand-decoration ((_ (eql 'inline)) name rest)
`((declaim (inline ,name)) ,#rest))
Likewise, if you want to export the name of the function being defined, you can export it after the function is defined (order is not really important here):
(defmethod expand-decoration ((_ (eql 'export)) name rest)
`(,#rest (export ',name)))
The resulting code allows you to have a single (progn ...) form with a defun in toplevel position:
CL-USER> (macroexpand '§inline §export (defun my-test-fn () "hello"))
(PROGN
(DECLAIM (INLINE MY-TEST-FN))
(DEFUN MY-TEST-FN () "hello")
(EXPORT 'MY-TEST-FN))

Related

Implement Lisp eval function in Common Lisp

I am trying to implement a eval function using CLISP.
My motivation: suppose I have a Lisp program like this:
(defun call (arg)
(cond
(some-condition (call (other (strange (functions (on arg)))))
(t nil)
)
)
(defun mysterious-function (arg)
(call (strange (functions (on arg))))
)
(mysterious-function 100) ; only this line can be changed
I want to know what is actually called in (mysterious-function 100).
Currently my idea looks like below, but the obstacles are:
How to look up a symbol (currently using eval)
How to grab a definition of a function (e.g. get something like (defun f (x))) and then parse it
How to detect macro and expand them
Am I in the correct direction?
(defun my-eval (body)
(cond
((typep body 'integer) body)
((typep body 'float) body)
((typep body 'rational) body)
((typep body 'complex) body)
((typep body 'boolean) body)
((typep body 'symbol) (eval body))
((typep body 'list) (eval body))
(t (error))
)
)
(my-eval '(mysterious-function 100))
Most of the cases in your code can be replaced with a single check: ((constantp body) body)
As for other cases:
You can use boundp to check if a symbol has a global value.
To look up a global symbol value you can use symbol-value.
fboundp can be used to check if a symbol is globally bound to a function
To look up a global function you can use symbol-function to access its function object and can sometimes use function-lambda-expression to retrieve a parseable source code list from the function object. Sometimes this will not work as built in CLISP functions can be defined in C.
To check if a symbol has an associated global macro, use macro-function (returns non-nil if it does).
To expand a macro form, use macroexpand.
You will probably also need to detect special operators with special-operator-p, and handle them accordingly.
I think what you are trying to do would be simplified if you restrict the code you interpret to macros and user-defined functions as much as possible.
I remember reading about a fast-eval function used in genetic programming to skip the macroexpansion phase of evaluating code, and its approach looked similar to what you seem to have in mind.

Does any Lisp allow mutually recursive macros?

In Common Lisp, a macro definition must have been seen before the first use. This allows a macro to refer to itself, but does not allow two macros to refer to each other. The restriction is slightly awkward, but understandable; it makes the macro system quite a bit easier to implement, and to understand how the implementation works.
Is there any Lisp family language in which two macros can refer to each other?
What is a macro?
A macro is just a function which is called on code rather than data.
E.g., when you write
(defmacro report (x)
(let ((var (gensym "REPORT-")))
`(let ((,var ,x))
(format t "~&~S=<~S>~%" ',x ,var)
,var)))
you are actually defining a function which looks something like
(defun macro-report (system::<macro-form> system::<env-arg>)
(declare (cons system::<macro-form>))
(declare (ignore system::<env-arg>))
(if (not (system::list-length-in-bounds-p system::<macro-form> 2 2 nil))
(system::macro-call-error system::<macro-form>)
(let* ((x (cadr system::<macro-form>)))
(block report
(let ((var (gensym "REPORT-")))
`(let ((,var ,x)) (format t "~&~s=<~s>~%" ',x ,var) ,var))))))
I.e., when you write, say,
(report (! 12))
lisp actually passes the form (! 12) as the 1st argument to macro-report which transforms it into:
(LET ((#:REPORT-2836 (! 12)))
(FORMAT T "~&~S=<~S>~%" '(! 12) #:REPORT-2836)
#:REPORT-2836)
and only then evaluates it to print (! 12)=<479001600> and return 479001600.
Recursion in macros
There is a difference whether a macro calls itself in implementation or in expansion.
E.g., a possible implementation of the macro and is:
(defmacro my-and (&rest args)
(cond ((null args) T)
((null (cdr args)) (car args))
(t
`(if ,(car args)
(my-and ,#(cdr args))
nil))))
Note that it may expand into itself:
(macroexpand '(my-and x y z))
==> (IF X (MY-AND Y Z) NIL) ; T
As you can see, the macroexpansion contains the macro being defined.
This is not a problem, e.g., (my-and 1 2 3) correctly evaluates to 3.
However, if we try to implement a macro using itself, e.g.,
(defmacro bad-macro (code)
(1+ (bad-macro code)))
you will get an error (a stack overflow or undefined function or ...) when you try to use it, depending on the implementation.
Here's why mutually recursive macros can't work in any useful way.
Consider what a system which wants to evaluate (or compile) Lisp code for a slightly simpler Lisp than CL (so I'm avoiding some of the subtleties that happen in CL), such as the definition of a function, needs to do. It has a very small number of things it knows how to do:
it knows how to call functions;
it knows how to evaluate a few sorts of literal objects;
it has some special rules for a few sorts of forms – what CL calls 'special forms', which (again in CL-speak) are forms whose car is a special operator;
finally it knows how to look to see whether forms correspond to functions which it can call to transform the code it is trying to evaluate or compile – some of these functions are predefined but additional ones can be defined.
So the way the evaluator works is by walking over the thing it needs to evaluate looking for these source-code-transforming things, aka macros (the last case), calling their functions and then recursing on the results until it ends up with code which has none left. What's left should consist only of instances of the first three cases, which it then knows how to deal with.
So now think about what the evaluator has to do if it is evaluating the definition of the function corresponding to a macro, called a. In Cl-speak it is evaluating or compiling a's macro function (which you can get at via (macro-function 'a) in CL). Let's assume that at some point there is a form (b ...) in this code, and that b is known also to correspond to a macro.
So at some point it comes to (b ...), and it knows that in order to do this it needs to call b's macro function. It binds suitable arguments and now it needs to evaluate the definition of the body of that function ...
... and when it does this it comes across an expression like (a ...). What should it do? It needs to call a's macro function, but it can't, because it doesn't yet know what it is, because it's in the middle of working that out: it could start trying to work it out again, but this is just a loop: it's not going to get anywhere where it hasn't already been.
Well, there's a horrible trick you could do to avoid this. The infinite regress above happens because the evaluator is trying to expand all of the macros ahead of time, and so there's no base to the recursion. But let's assume that the definition of a's macro function has code which looks like this:
(if <something>
(b ...)
<something not involving b>)
Rather than doing the expand-all-the-macros-first trick, what you could do is to expand only the macros you need, just before you need their results. And if <something> turned out always to be false, then you never need to expand (b ...), so you never get into this vicious loop: the recursion bottoms out.
But this means you must always expand macros on demand: you can never do it ahead of time, and because macros expand to source code you can never compile. In other words a strategy like this is not compatible with compilation. It also means that if <something> ever turns out to be true then you'll end up in the infinite regress again.
Note that this is completely different to macros which expand to code which involves the same macro, or another macro which expands into code which uses it. Here's a definition of a macro called et which does that (it doesn't need to do this of course, this is just to see it happen):
(defmacro et (&rest forms)
(if (null forms)
't
`(et1 ,(first forms) ,(rest forms))))
(defmacro et1 (form more)
(let ((rn (make-symbol "R")))
`(let ((,rn ,form))
(if ,rn
,rn
(et ,#more)))))
Now (et a b c) expands to (et1 a (b c)) which expands to (let ((#:r a)) (if #:r #:r (et b c))) (where all the uninterned things are the same thing) and so on until you get
(let ((#:r a))
(if #:r
#:r
(let ((#:r b))
(if #:r
#:r
(let ((#:r c))
(if #:r
#:r
t))))))
Where now not all the uninterned symbols are the same
And with a plausible macro for let (let is in fact a special operator in CL) this can get turned even further into
((lambda (#:r)
(if #:r
#:r
((lambda (#:r)
(if #:r
#:r
((lambda (#:r)
(if #:r
#:r
t))
c)))
b)))
a)
And this is an example of 'things the system knows how to deal with': all that's left here is variables, lambda, a primitive conditional and function calls.
One of the nice things about CL is that, although there is a lot of useful sugar, you can still poke around in the guts of things if you like. And in particular, you still see that macros are just functions that transform source code. The following does exactly what the defmacro versions do (not quite: defmacro does the necessary cleverness to make sure the macros are available early enough: I'd need to use eval-when to do that with the below):
(setf (macro-function 'et)
(lambda (expression environment)
(declare (ignore environment))
(let ((forms (rest expression)))
(if (null forms)
't
`(et1 ,(first forms) ,(rest forms))))))
(setf (macro-function 'et1)
(lambda (expression environment)
(declare (ignore environment))
(destructuring-bind (_ form more) expression
(declare (ignore _))
(let ((rn (make-symbol "R")))
`(let ((,rn ,form))
(if ,rn
,rn
(et ,#more)))))))
There have been historic Lisp systems that allow this, at least in interpreted code.
We can allow a macro to use itself for its own definition, or two or more macros to mutually use each other, if we follow an extremely late expansion strategy.
That is to say, our macro system expands a macro call just before it is evaluated (and does that each time that same expression is evaluated).
(Such a macro expansion strategy is good for interactive development with macros. If you fix a buggy macro, then all code depending on it automatically benefits from the change, without having to be re-processed in any way.)
Under such a macro system, suppose we have a conditional like this:
(if (condition)
(macro1 ...)
(macro2 ...))
When (condition) is evaluated, then if it yields true, (macro1 ...) is evaluated, otherwise (macro2 ...). But evaluation also means expansion. Thus only one of these two macros is expanded.
This is the key to why mutual references among macros can work: we are able rely on the conditional logic to give us not only conditional evaluation, but conditional expansion also, which then allows the recursion to have ways of terminating.
For example, suppose macro A's body of code is defined with the help of macro B, and vice versa. And when a particular invocation of A is executed, it happens to hit the particular case that requires B, and so that B call is expanded by invocation of macro B. B also hits the code case that depends on A, and so it recurses into A to obtain the needed expansion. But, this time, A is called in a way that avoids requiring, again, an expansion of B; it avoids evaluating any sub-expression containing the B macro. Thus, it calculates the expansion, and returns it to B, which then calculates its expansion returns to the outermost A. A finally expands and the recursion terminates; all is well.
What blocks macros from using each other is the unconditional expansion strategy: the strategy of fully expanding entire top-level forms after they are read, so that the definitions of functions and macros contain only expanded code. In that situation there is no possibility of conditional expansion that would allow for the recursion to terminate.
Note, by the way, that a macro system which expands late doesn't recursively expand macros in a macro expansion. Suppose (mac1 x y) expands into (if x (mac2 y) (mac3 y)). Well, that's all the expansion that is done for now: the if that pops out is not a macro, so expansion stops, and evaluation proceeds. If x yields true, then mac2 is expanded, and mac3 is not.

How do I define a function that creates a function alias?

The Lisp forum thread Define macro alias? has an example of creating function alias using a form such as
(setf (symbol-function 'zero?) #'zerop)
This works fine, making zero? a valid predicate. Is it possible to parametrize this form without resorting to macros? I'd like to be able to call the following and have it create function?:
(define-predicate-alias 'functionp)`
My take was approximately:
(defun defalias (old new)
(setf (symbol-function (make-symbol new))
(symbol-function old)))
(defun define-predicate-alias (predicate-function-name)
(let ((alias (format nil "~A?" (string-right-trim "-pP" predicate-function-name))))
(defalias predicate-function-name alias)))
(define-predicate-alias 'zerop)
(zero? '())
This fails when trying to call zero? saying
The function COMMON-LISP-USER::ZERO? is undefined.
make-symbol creates an uninterned symbol. That's why zero? is undefined.
Replace your (make-symbol new) with e.g. (intern new *package*). (Or you may want to think more carefully in which package to intern your new symbol.)
Your code makes a symbol, via MAKE-SYMBOL, but you don't put it into a package.
Use the function INTERN to add a symbol to a package.
To expand on Lars' answer, choose the right package. In this case the default might be to use the same package from the aliased function:
About style:
Anything that begins with DEF should actually be a macro. If you have a function, don't use a name beginning with "DEF". If you look at the Common Lisp language, all those are macro. For example: With those defining forms, one would typically expect that they have a side-effect during compilation of files: the compiler gets informed about them. A function can't.
If I put something like this in a file
(define-predicate-alias zerop)
(zero? '())
and then compile the file, I would expect to not see any warnings about an undefined ZERO?. Thus a macro needs to expand (define-predicate-alias 'zerop) into something which makes the new ZERO? known into the compile-time environment.
I would also make the new name the first argument.
Thus use something like MAKE-PREDICATE-ALIAS instead of DEFINE-PREDICATE-ALIAS, for the function.
There are already some answers that explain how you can do this, but I'd point out:
Naming conventions, P, and -P
Common Lisp has a naming convention that is mostly adhered to (there are exceptions, even in the standard library), that if a type name is multiple words (contains a -), then its predicate is named with -P suffix, whereas if it doesn't, the suffix is just P. So we'd have keyboardp and lcd-monitor-p. It's good then, that you're using (string-right-trim "-pP" predicate-function-name)), but since the …P and …-P names in the standard, and those generated by, e.g., defstruct, will be using P, not p, you might just use (string-right-trim "-P" predicate-function-name)). Of course, even this has the possible issues with some names (e.g., pop), but I guess that just comes with the territory.
Symbol names, format, and *print-case*
More importantly, using format to create symbol names for subsequent interning is dangerous, because format doesn't always print a symbol's name with the characters in the same case that they actually appear in its name. E.g.,
(let ((*print-case* :downcase))
(list (intern (symbol-name 'foo))
(intern (format nil "~A" 'foo))))
;=> (FOO |foo|) ; first symbol has name "FOO", second has name "foo"
You may be better off using string concatenation and extracting symbol names directly. This means you could write code like (this is slightly different use case, since the other questions already explain how you can do what you're trying to do):
(defmacro defpredicate (symbol)
(flet ((predicate-name (symbol)
(let* ((name (symbol-name symbol))
(suffix (if (find #\- name) "-P" "P")))
(intern (concatenate 'string name suffix)))))
`(defun ,(predicate-name symbol) (x)
(typep x ',symbol)))) ; however you're checking the type
(macroexpand-1 '(defpredicate zero))
;=> (DEFUN ZEROP (X) (TYPEP X 'ZERO))
(macroexpand-1 '(defpredicate lcd-monitor))
;=> (DEFUN LCD-MONITOR-P (X) (TYPEP X 'LCD-MONITOR))

Lisp evaluate variable in macro expression

I have the following function (I am a very beginner at Lisp):
(defun my-fun (a b)
(my-commandsend-and-reply-macro (cmd)
(:reply (ok result)
(do-something a b result)))
)
where my-commandsend-and-reply-macro is a macro written by another programmer. I am unable to modify it.
my-commandsend-and-reply-macro sends a command (in this example cmd) to a server process (it is written in another programming language) and then waits for its answer.
The answer is processed then in the macro using the user-given ":reply part of the code". The list (ok result) is a kind of pattern, in the macro a destructuring-bind destructures and binds the proper parts of the answer to ok and result (ok is just a flag). After this the other user-given lines of the ":reply part" are excuted. (for result processing)
I would like to do the following:
1, send a command like to the other process (this is ok)
2, call a function (like do-something) using the result AND using some other parameters which are the actual parameters of my-fun (this part fails...)
How can I do this? I think the problem is that a and b are not evaluated before the macro expansion and when the macro is expanded Lisp searches for a local a and b but there is no a or b. Is there any way to evaluate a and b? (so the macro could treat them like concrete values)
This is the macro def: (written by another programmer)
(defmacro* my-commandsend-and-reply-macro ((cmd &rest args) &body body)
`(progn
(with-request-id ()
(setf (gethash *request-id* *my-callbacks*)
(lambda (status &rest status-args)
(case status
,#(loop for (kind . clause) in body when (eql kind :reply)
collect
(destructuring-bind
((status-flag &rest lambda-form-pattern)
&body action-given-by-user) clause
`(,status-flag
(destructuring-bind ,lambda-form-pattern status-args
,#action-given-by-user))))
((error)
(message "Error: %s" (elt (elt status-args 0) 1))))))
(apply #'send-command-to-process *request-id* cmd args)))))
Def of with-request-id:
(defmacro* with-request-id ((&rest vars) &body body)
"Send `getid' to the server, and call `body' once the response
with the new ID has arrived. By then, global variable `*request-id*'
is bound to the latest request ID."
`(progn
(when (not (server-is-running))
(error "Server isn't running!"))
(when *reqid-queue*
(error "Some internal error occured. Please, restart the program!"))
(lexical-let (,#(loop for var in vars
collect `(,var ,var)))
(setf *reqid-queue* (lambda ()
(unwind-protect
(progn ,#body)
(setf *reqid-queue* nil)))))
(get-id)))
And getting id from the other process:
(defun get-id ()
(send-command-to-process 'getid))
Without looking into your code at all (apologies -- no time) ---
a and b are evaluated by the function my-fun. All functions evaluate their arguments to begin with -- only macros and special forms do not necessarily evaluate all of their arguments.
But those a and b values are not passed to the macro -- the only thing passed to it is the unevaluated sexp that is bound to cmd. And you do not even define cmd in your function!
What you need to do is substitute the values of a and b into the cmd sexp. You have not shown how cmd is defined/constructed, at all. Construct it using the values of a and b, and you should be OK.
To construct the cmd sexp, remember that you can use backquote syntax to simplify things, using comma syntax to pass the values of a and b. E.g.
(let ((cmd `(some funny (expression) that ((uses)) ,a AND ,b)))
code-that-uses-CMD)
This assumes that the code you pass to the macro does not need the variables a and b, and it needs only their values.
When the function my-fun is called the arguments have already been evaluated so it's not clear to me what is the problem you are facing.
The only strange thing I see is that the macro is un-hygienic and so if your arguments are named instead of a and b for example status or status-args you're going to be in trouble because the expression
(do-something <a> <b> results)
will be compiled in a context where those names have been reused by the macro.

How can I destructure an &rest argument of varying length in my elisp macro?

I have a program that takes as inputs a chunk of data and a list of rules, applying both a set of standard rules and the rules given as input to the chunk of data. The size of both inputs may vary.
I want to be able to write a list of rules like this:
(rule-generating-macro
(rule-1-name rule-1-target
(rule-action-macro (progn actions more-actions)))
(rule-2-name rule-2-target
(rule-action-macro (or (action-2) (default-action))))
;; more rules
)
Right now, rules are more verbose -- they look more like
(defvar rule-list
`((rule-1-name rule-1-target
,#(rule-action-macro (progn actions more-actions)))
(rule-2-name rule-2-target
,#(rule-action-macro (or (action-2) (default-action))))
;; more rules
)
The latter form looks uglier to me, but I can't figure out how to write a macro that can handle a variable-length &rest argument, iterate over it, and return the transformed structure. Using a defun instead of a defmacro isn't really on the table because (as hopefully the example shows) I'm trying to control evaluation of the list of rules instead of evaluating the list when my program first sees it, and once you need to control evaluation, you're in defmacro territory. In this case, the thorny point is the rule-action-macro part - getting the interpreter to read that and use its expanded value has been problematic.
How can I create a macro that handles a variable-length argument so that I can write rule lists in a concise way?
defmacro will happily accept a &rest argument
(see Defining Macros for Emacs Lisp and Macro Lambda Lists for Common Lisp).
Then you can do pretty much anything you want with it in the macro body - e.g., iterate over it. Remember, macro is much more than just backquote!
E.g.:
(defmacro multidefvar (&rest vars)
(let ((forms (mapcar (lambda (var) `(defvar ,var)) vars)))
`(progn ,#forms)))
(macroexpand '(multidefvar a b c d))
==> (PROGN (DEFVAR A) (DEFVAR B) (DEFVAR C) (DEFVAR D))