Use a clojure macro to automatically create getters and setters inside a reify call - macros

I am trying to implement a huge Java interface with numerous (~50) getter and setter methods (some with irregular names). I thought it would be nice to use a macro to reduce the amount of code. So instead of
(def data (atom {:x nil}))
(reify HugeInterface
(getX [this] (:x #data))
(setX [this v] (swap! data assoc :x v)))
I want to be able to write
(def data (atom {:x nil}))
(reify HugeInterface
(set-and-get getX setX :x))
Is this set-and-get macro (or something similar) possible? I haven't been able to make it work.

(Updated with a second approach -- see below the second horizontal rule -- as well as some explanatory remarks re: the first one.)
I wonder if this might be a step in the right direction:
(defmacro reify-from-maps [iface implicits-map emit-map & ms]
`(reify ~iface
~#(apply concat
(for [[mname & args :as m] ms]
(if-let [emit ((keyword mname) emit-map)]
(apply emit implicits-map args)
[m])))))
(def emit-atom-g&ss
{:set-and-get (fn [implicits-map gname sname k]
[`(~gname [~'this] (~k #~(:atom-name implicits-map)))
`(~sname [~'this ~'v]
(swap! ~(:atom-name implicits-map) assoc ~k ~'v))])})
(defmacro atom-bean [iface a & ms]
`(reify-from-maps ~iface {:atom-name ~a} ~emit-atom-g&ss ~#ms))
NB. that the atom-bean macro passes the actual compile-time value of emit-atom-g&ss on to reify-from-maps. Once a particular atom-bean form is compiled, any subsequent changes to emit-atom-g&ss have no effect on the behaviour of the created object.
An example macroexpansion from the REPL (with some line breaks and indentation added for clarity):
user> (-> '(atom-bean HugeInterface data
(set-and-get setX getX :x))
macroexpand-1
macroexpand-1)
(clojure.core/reify HugeInterface
(setX [this] (:x (clojure.core/deref data)))
(getX [this v] (clojure.core/swap! data clojure.core/assoc :x v)))
Two macroexpand-1s are necessary, because atom-bean is a macro which expands to a further macro call. macroexpand would not be particularly useful, as it would expand this all the way to a call to reify*, the implementation detail behind reify.
The idea here is that you can supply an emit-map like emit-atom-g&ss above, keyed by keywords whose names (in symbolic form) will trigger magic method generation in reify-from-maps calls. The magic is performed by the functions stored as functions in the given emit-map; the arguments to the functions are a map of "implicits" (basically any and all information which should be accessible to all method definitions in a reify-from-maps form, like the name of the atom in this particular case) followed by whichever arguments were given to the "magic method specifier" in the reify-from-maps form. As mentioned above, reify-from-maps needs to see an actual keyword -> function map, not its symbolic name; so, it's only really usable with literal maps, inside other macros or with help of eval.
Normal method definitions can still be included and will be treated as in a regular reify form, provided keys matching their names do not occur in the emit-map. The emit functions must return seqables (e.g. vectors) of method definitions in the format expected by reify: in this way, the case with multiple method definitions returned for one "magic method specifier" is relatively simple. If the iface argument were replaced with ifaces and ~iface with ~#ifaces in reify-from-maps' body, multiple interfaces could be specified for implementation.
Here's another approach, possibly easier to reason about:
(defn compile-atom-bean-converter [ifaces get-set-map]
(eval
(let [asym (gensym)]
`(fn [~asym]
(reify ~#ifaces
~#(apply concat
(for [[k [g s]] get-set-map]
[`(~g [~'this] (~k #~asym))
`(~s [~'this ~'v]
(swap! ~asym assoc ~k ~'v))])))))))
This calls on the compiler at runtime, which is somewhat expensive, but only needs to be done once per set of interfaces to be implemented. The result is a function which takes an atom as an argument and reifies a wrapper around the atom implementing the given interfaces with getters and setters as specified in the get-set-map argument. (Written this way, this is less flexible than the previous approach, but most of the code above could be reused here.)
Here's a sample interface and a getter/setter map:
(definterface IFunky
(getFoo [])
(^void setFoo [v])
(getFunkyBar [])
(^void setWeirdBar [v]))
(def gsm
'{:foo [getFoo setFoo]
:bar [getFunkyBar setWeirdBar]})
And some REPL interactions:
user> (def data {:foo 1 :bar 2})
#'user/data
user> (def atom-bean-converter (compile-atom-bean-converter '[IFunky] gsm))
#'user/atom-bean-converter
user> (def atom-bean (atom-bean-converter data))
#'user/atom-bean
user> (.setFoo data-bean 3)
nil
user> (.getFoo atom-bean)
3
user> (.getFunkyBar data-bean)
2
user> (.setWeirdBar data-bean 5)
nil
user> (.getFunkyBar data-bean)
5

The point is reify being a macro itself which is expanded before your own set-and-get macro - so the set-and-get approach doesn't work. So, instead of an inner macro inside reify, you need a macro on the "outside" that generates the reify, too.

Since the trick is to expand the body before reify sees it, a more general solution could be something along these lines:
(defmacro reify+ [& body]
`(reify ~#(map macroexpand-1 body)))

You can also try to force your macro to expand first:
(ns qqq (:use clojure.walk))
(defmacro expand-first [the-set & code] `(do ~#(prewalk #(if (and (list? %) (contains? the-set (first %))) (macroexpand-all %) %) code)))
(defmacro setter [setterf kw] `(~setterf [~'this ~'v] (swap! ~'data assoc ~kw ~'v)))
(defmacro getter [getterf kw] `(~getterf [~'this] (~kw #~'data)))
(expand-first #{setter getter}
(reify HugeInterface
(getter getX :x)
(setter setX :x)))

Related

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.

Local context in a literal tag

Can literal tags capture local context bindings, so for instance if i have a tag #my/closuretag whose reader function is closuretag
(defrecord MyRecord [f])
(defn closuretag [f] (MyRecord. (eval f)))
For above defintions, #my/closuretag inc would work fine but
(let [foo 1] #my/closuretag #(inc foo)) would fail.
Can a literal tag be made to work for this case? May be by a macro instead of a plain reader function?
Edit:
Here is something weird, If i change closuretag function to (defn closuretag [f] f), I get a proper closure with scoped variables bound inside the function which is callable! Why does using record here causing f to be a list of symbols?!
I am guessing that we should infer from literal tag vs. tagged element and the behavior described in your edit, that you are referring to readers installed in data_readers.clj, and not readers for data through (edn/) read or read-string.
Since these are reader functions, they are going to behave like macros in that you can conceptually consider the arguments to be quoted and results evaluated as code.
So, you want this
(defrecord MyRecord [f])
(defn my-tag-reader [f] (list ->MyRecord f))
To get the behavior of this
(def my-record (let [foo 1] #my/example-tag #(inc foo)))
((:f my-record)) ;=> 2
When my-tag-reader is the (namespaced qualified) reader function of #my/example-tag in the data_readers.clj map.

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))

lisp macro expand with partial eval

I have following code which confuse me now, I hope some can tell me the difference and how to fix this.
(defmacro tm(a)
`(concat ,(symbol-name a)))
(defun tf(a)
(list (quote concat) (symbol-name a)))
I just think they should be the same effect, but actually they seem not.
I try to following call:
CL-USER> (tf 'foo)
(CONCAT "FOO")
CL-USER> (tm 'foo)
value 'FOO is not of the expected type SYMBOL.
[Condition of type TYPE-ERROR]
So, what's the problem?
What i want is:
(tm 'foo) ==> (CONCAT "FOO")
The first problem is that 'foo is expanded by the reader to (quote foo), which is not a symbol, but a list. The macro tries to expand (tm (quote foo)). The list (quote foo) is passed as the parameter a to the macro expansion function, which tries to get its symbol-name. A list is not a valid argument for symbol-name. Therefore, your macro expansion fails.
The second problem is that while (tm foo) (note: no quote) does expand to (concat "FOO"), this form will then be executed by the REPL, so that this is also not the same as your tf function. This is not surprising, of course, because macros do different things than functions.
First, note that
`(concat ,(symbol-name a))
and
(list (quote concat) (symbol-name a))
do the exact same thing. They are equivalent pieces of code (backquote syntax isn't restricted to macro bodies!): Both construct a list whose first element is the symbol CONCAT and whose second element is the symbol name of whatever the variable A refers to.
Clearly, this only makes sense if A refers to a symbol, which, as Svante has pointed out, isn't the case in the macro call example.
You could, of course, extract the symbol from the list (QUOTE FOO), but that prevents you from calling the macro like this:
(let ((x 'foo))
(tm x))
which raises the question of why you would event want to force the user of the macro to explicitly quote the symbol where it needs to be a literal constant anyway.
Second, the way macros work is this: They take pieces of code (such as (QUOTE FOO)) as arguments and produce a new piece of code that, upon macroexpansion, (more or less) replaces the macro call in the source code. It is often useful to reuse macro arguments within the generated code by putting them where they are going to be evaluated later, such as in
(defmacro tm2 (a)
`(print (symbol-name ,a)))
Think about what this piece of code does and whether or not my let example above works now. That should get you on the right track.
Finally, a piece of advice: Avoid macros when a function will do. It will make life much easier for both the implementer and the user.

In clojure, how can I evaluate the arguments to a macro from another macro?

I have two macros. The first one takes a symbol as the only parameter (because it's passed to def, which needs a symbol). The second function takes a list of symbols and should call the first with each symbol individually.
(defmacro m1 [s]
'(let [f# ... dynamic function definition ...]
(def ~s f#))
The second macro should take a list of symbols and pass them to the first, but I can't get it to work. The best I could come up with was the following:
(defmacro m2 [symbols]
`(for [s# ~symbols] (eval (read-string (str "(name.of.current.namespace/m1 " s# ")")))))
which forces the s# to be evaluated before it is passed to the first macro. It is also invoked with a list of strings, rather than a list of symbols.
This is useful for a library which I am using for which all of the functions in the library takes the same two first parameters. I am trying to create wrapper functions, in my namespace, for some of the functions, which automatically provides the first two parameter values which are common to all of them.
Any ideas to improve this?
Usually when you ask how to get two macros to cooperate, the answer is to not make them both macros. I think my blog post on macro-writing macros will help clarify. For this particular situation I'd probably combine two suggestions from the comments:
(defmacro build-simpler-functions [& names]
(cons 'do
(for [name names]
`(def ~(symbol (str "simple-" name))
(partial ~name 5 10))))) ; if you always pass 5 and 10
(build-simpler-functions f1 f2)
This expands to
(do
(def simple-f1 (clojure.core/partial f1 5 10))
(def simple-f2 (clojure.core/partial f2 5 10)))
which looks like basically what you want.
Edit: if the args you "always" pass are different for each function, you can do this:
(defmacro build-simpler-functions [& names]
(cons 'do
(for [[name & args] names]
`(def ~(symbol (str "simple-" name))
(partial ~name ~#args)))))
(build-simpler-functions [f1 5 10] [f2 "Yo dawg"]) ; expansion similar to the previous