LISP: how to trace macros - macros

This is probably a stupid question, but I'm walking through the PG lisp book, and I wanted to step through some example macros that he provides with actual values, for instance:
(defmacro our-let (binds &body body)
`(
(lambda ,(
mapcar #'(lambda (x) (if (consp x) (car x) x)) binds
)
,#body
)
,#(mapcar #'(lambda (x) (if (consp x) (cadr x) nil)) binds)
)
)
I naively tried to run (trace our-let) and then (our-let ((x 1) (y 2)) (+ x y)) but I'm getting an error, can't use encapsulation to trace anonymous function #<FUNCTION (MACRO-FUNCTION OUR-LET) {22675BBB}>. Also not sure how to best put print statements into the lambdas. What's the best way to debug this macro/output how it's processing inputs?
EDIT(1): I had the incorrect formatting for macroexpand, which works.

Actually being able to trace macros is not very common in Common Lisp implementations. Compilers will typically expand the macro forms during compilation.
A few implementations support it though - which makes sense when they also support a Lisp interpreter, which runs the actual source. Among those are LispWorks and CLISP.
Here using the code from Sylwester in CLISP:
i i i i i i i ooooo o ooooooo ooooo ooooo
I I I I I I I 8 8 8 8 8 o 8 8
I \ `+' / I 8 8 8 8 8 8
\ `-+-' / 8 8 8 ooooo 8oooo
`-__|__-' 8 8 8 8 8
| 8 o 8 8 o 8 8
------+------ ooooo 8oooooo ooo8ooo ooooo 8
Welcome to GNU CLISP 2.49.93+ (2018-02-18) <http://clisp.org/>
Copyright (c) Bruno Haible, Michael Stoll 1992-1993
Copyright (c) Bruno Haible, Marcus Daniels 1994-1997
Copyright (c) Bruno Haible, Pierpaolo Bernardi, Sam Steingold 1998
Copyright (c) Bruno Haible, Sam Steingold 1999-2000
Copyright (c) Sam Steingold, Bruno Haible 2001-2018
Type :h and hit Enter for context help.
[1]> (defmacro our-let ((&rest bindings) &body body)
(let ((names (mapcar #'(lambda (x) (if (consp x) (car x) x)) bindings))
(exprs (mapcar #'(lambda (x) (if (consp x) (cadr x) nil)) bindings)))
`((lambda ,names ,#body) ,#exprs)))
OUR-LET
[2]> (trace our-let)
;; Tracing macro OUR-LET.
(OUR-LET)
[3]> (dotimes (i 3)
(our-let ((x (* i 10)))
(+ x 3)))
1. Trace: (OUR-LET ((X (* I 10))) (+ X 3))
1. Trace: OUR-LET ==> ((LAMBDA (X) (+ X 3)) (* I 10))
1. Trace: (OUR-LET ((X (* I 10))) (+ X 3))
1. Trace: OUR-LET ==> ((LAMBDA (X) (+ X 3)) (* I 10))
1. Trace: (OUR-LET ((X (* I 10))) (+ X 3))
1. Trace: OUR-LET ==> ((LAMBDA (X) (+ X 3)) (* I 10))
NIL
[4]>

How you debug it:
(macroexpand-1 '(our-let ((x 1) (y 2)) (+ x y)))
; ==> ((lambda (X Y) (+ X Y)) 1 2)
; ==> t
BTW your formatting is not good. Here is how it can look:
(defmacro our-let (binds &body body)
`((lambda ,(mapcar #'(lambda (x) (if (consp x) (car x) x)) binds)
,#body)
,#(mapcar #'(lambda (x) (if (consp x) (cadr x) nil)) binds)))
Or I would prefer:
(defmacro our-let ((&rest bindings) &body body)
(let ((names (mapcar #'(lambda (x) (if (consp x) (car x) x)) bindings))
(exprs (mapcar #'(lambda (x) (if (consp x) (cadr x) nil)) bindings)))
`((lambda ,names ,#body) ,#exprs)))

A nice thing about CL is that its designers thought quite hard about some things. In particular it turns out that you can trace macroexpansion portably in CL, thanks to *macroexpand-hook*. The code at the end of this answer uses it to trace macroexpansion It makes some attempt to cooperate with anything else which might be talking to *macroexpand-hook*, and to avoid recursive tracing, but it's not very well tested. There are controls for how much should be printed which have default values which are 'much less than everything'.
Here is an example of this in LispWorks:
> (macroexpand-traced-p)
nil
> (trace-macroexpand)
t
> (defun foo (x) x)
(defun foo (x) ...)
-> (dspec:def (defun foo) (dspec:install-defun 'foo # ...))
(dspec:def (defun foo) (dspec:install-defun 'foo # ...))
-> (compiler-let (#) (compiler::top-level-form-name # #))
(compiler::top-level-form-name (defun foo)
(dspec:install-defun 'foo # ...))
-> (compiler::tlf-name-binding (compiler-let #)
(dspec:install-defun 'foo # ...))
(compiler::tlf-name-binding (compiler-let #)
(dspec:install-defun 'foo # ...))
-> (compiler-let (# #) (dspec:install-defun 'foo # ...))
(dspec:location)
-> ':listener
foo
As you can see you get a lot of internal expansions which are probably not interesting. To deal with this there is support for filtering the output so you don't see macroexpansions which may not be interesting to you, of which there are a lot.
Here is a filter function which tries to only show expansions where the thing being expanded is visible in the current package:
(defun trace-macroexpand-trace-this-package-p (macro-function macro-form
environment)
(declare (ignore macro-function environment))
(and (consp macro-form)
(symbolp (first macro-form))
(let ((name (first macro-form)))
(eq (find-symbol (symbol-name name) *package*) name))))
And here is the some output for that:
> (setf *trace-macroexpand-trace-p* #'trace-macroexpand-trace-this-package-p)
(setf *trace-macroexpand-trace-p*
#'trace-macroexpand-trace-this-package-p)
-> (let* (#) (setq *trace-macroexpand-trace-p* #:|Store-Var-1102|))
#<Function trace-macroexpand-trace-this-package-p 4060000844>
> (defun foo (x) x)
(defun foo (x) ...)
-> (dspec:def (defun foo) (dspec:install-defun 'foo # ...))
foo
As you can see you only now get 'interesting' macroexpansions. Cleverer filters could be defined, of course.
Here is the code:
(eval-when (:load-toplevel :compile-toplevel :execute)
;; macroexpansion tracing really wants to be off when compiling this
;; code as exciting things may happen during the evaluation of
;; DEFVAR &c otherwise.
(when (fboundp 'trace-macroexpand)
(ignore-errors ;don't barf
(trace-macroexpand nil))))
(defvar *trace-macroexpand-print-length* 3
"The value of *PRINT-LENGTH* used when tracing macroexpansions")
(defvar *trace-macroexpand-print-level* 2
"The value of *PRINT-LEVEL* used when tracing macroexpansions")
(defvar *trace-macroexpand-trace-p* (constantly t)
"Should we trace a given macroexpansion?
If this is bound to a function that function will be called with the
same three arguments that *MACROEXPAND-HOOK* takes, and should return
true if the expansion is to be printed. Otherwise it should be true
if expansion is to be printed, false otherwise.")
(defvar *traced-macroexpand-hook*
;; the old value of *MACROEXPAND-HOOK*, used to restore it and to
;; know if we should trace. Not user-adjustable.
nil)
(defun trace-macroexpand (&optional (tracep t))
"Trace or untrace macroexpansion.
If called with no argument, or an argument which is true, ensure that
macroexpansion is on. If it was already on return NIL, otherwise
return T.
If called with an argument which is NIL then ensure macroexpansion is
not traced. If it was traced return T else return NIL."
(if tracep
(if *traced-macroexpand-hook*
nil
(let ((hook *macroexpand-hook*))
(flet ((macroexpand-hook (macro-function macro-form environment)
(if (if (functionp *trace-macroexpand-trace-p*)
(funcall *trace-macroexpand-trace-p*
macro-function macro-form environment)
*trace-macroexpand-trace-p*)
(let ((expanded-form (funcall hook macro-function
macro-form environment))
(*print-length* *trace-macroexpand-print-length*)
(*print-level* *trace-macroexpand-print-level*)
(*print-pretty* t))
(format *debug-io* "~&~S~% -> ~S~%" macro-form expanded-form)
expanded-form)
(funcall hook macro-function macro-form environment))))
(setf *traced-macroexpand-hook* hook
*macroexpand-hook* #'macroexpand-hook)
t)))
(if *traced-macroexpand-hook*
(progn
(setf *macroexpand-hook* *traced-macroexpand-hook*
*traced-macroexpand-hook* nil)
t)
nil)))
(defun macroexpand-traced-p ()
"Is macroexpansion currently traced?"
(if *traced-macroexpand-hook* t nil))

Here is one way to trace the macro that should work in any Common Lisp:
(eval-when (:compile-toplevel :load-toplevel :execute)
(defun our-let-expander (binds body)
`((lambda ,(mapcar #'(lambda (x) (if (consp x) (car x) x)) binds)
,#body)
,#(mapcar #'(lambda (x) (if (consp x) (cadr x) nil)) binds))))
(defmacro our-let (binds &body body)
(our-let-expander binds body))
Now we just (trace our-let-expander).
In my experience, complicated macros often end up handled via expander helper functions like this anyway, for various reasons.
(One big reason is this: as soon as you have two or more syntactic interfaces to the same expansion logic, you don't want to copy and paste that logic into multiple defmacro forms, but have it in a function.)
P.S. note the reformatting of the backquote form. Do not separate opening parentheses from what follows, and have closing parentheses on lines by themselves.

Related

Common Lisp macro let-curry - not working

I found myself calling lots of methods whose first argument is a complex object from a given class.
Whilst with-slots and with-accessors are useful, generic methods cannot be bound in this way. So I thought: if we could locally curry any functions, slots + accessors + generic functions + functions could all be addressed with the same construct.
Example of code I want to clean up:
(defun clox-string (scanner)
"Parse string into a token and add it to tokens"
(loop while (and (char/= #\" (peek scanner))
(not (at-end-p scanner)))
do
(if (char= #\Newline (peek scanner)) (incf (line scanner))
(advance scanner)))
(when (at-end-p scanner)
(clox.error::clox-error (line scanner) "Unterminated string.")
(return-from clox-string nil))
(advance scanner) ;; consume closing "
(add-token scanner 'STRING (subseq (source scanner)
(1+ (start scanner))
(1- (current scanner)))))
This would be cleaner (I'm imitating this in CL https://craftinginterpreters.com/scanning.html#reserved-words-and-identifiers but I often end up with more verbose and less readable code than in Java - specially when using this classes a lot). As in CL methods don't belong to classes you end up declaring such arguments over and over. This would be a bit better:
(defun clox-string (scanner)
"Parse string into a token and add it to tokens"
(let-curry scanner (peek at-end-p line source start current advance add-token)
(loop while (and (char/= #\" (peek))
(not (at-end-p)))
do
(if (char= #\Newline (peek)) (incf (line))
(advance)))
(when (at-end-p)
(clox.error::clox-error (line) "Unterminated string.")
(return-from clox-string nil))
(advance) ;; consume closing "
(add-token 'STRING (subseq (source)
(1+ (start))
(1- (current)))))
sketch of macro (not working):
;; Clearly not as I don't understand macros very well :) non-working code:
(defmacro let-curry (obj functions &body body)
"Locally curry all functions"
(let ((fn (gensym)))
`(flet (loop
for ,fn in ,functions
collect (list ,fn (&rest args)
(funcall ,fn ,obj args)))
,#body)))
EDIT (ADD): Notice that scanner is a class; start, source, line, etc., accessors to the slots with the same name; add-token a generic function of more than one argument, advance a generic method of one argument:
(defclass scanner ()
((source
:initarg :source
:accessor source)
...
(...)))
(defmethod advance ((scanner scanner)) ...)
(defmethod add-token ((scanner scanner) token-type) ...)
Simpler Example with error:
;; With
(defun add (x y) (+ x y))
(defun mul (x y) (* x y))
;; I want to have this:
(let-curry 1000 (add mul)
(print (add 3))
(print (mul 3)))
;; expanding to:
(flet ((add (y) (add 1000 y))
(mul (y) (mul 1000 y)))
(print (add 3))
(print (mul 3)))
;; but instead I'm getting:
Execution of a form compiled with errors.
Form:
(FLET (LOOP
FOR
#1=#:G777
IN
(ADD MUL
)
COLLECT
(LIST #1#
(&REST ARGS)
(FUNCALL #1# 1000 ARGS)))
(PRINT (ADD 3))
(PRINT (MUL 3)))
Compile-time error:
The FLET definition spec LOOP is malformed.
[Condition of type SB-INT:COMPILED-PROGRAM-ERROR]
Thanks! The basic question is: is it possible to make such macro work?
Your version didn't expand to what you wanted but:
(flet (loop for #:g8307 in (add mul) collect (list #:g8307 (&rest args) (funcall #:g8307 1000 args)))
(print (add 3)) (print (mul 3)))
Now the loop needs to be done at macro expansion time.
Here is a working version:
(defmacro let-curry (obj (&rest functions) &body body)
"Locally curry all functions"
`(flet ,(loop for fn in functions
collect `(,fn (&rest args)
(apply #',fn ,obj args)))
,#body))
;; test it using add and mul from OP
(macroexpand-1 '(let-curry 10 (add mul) (list (add 5) (mul 5))))
;; ==>
(flet ((add (&rest args) (apply #'add 10 args))
(mul (&rest args) (apply #'mul 10 args)))
(list (add 5) (mul 5)))
(let-curry 10 (add mul) (list (add 5) (mul 5)))
;; ==> (15 50)
Using gensym is only needed if you are in danger of shadowing/colliding something or to ensure evaluation order is least surprising, but in your case you actually want to shadow the original names with the curried version so it makes sense to just use the original name.
If you want to have more than one argument you should use apply
since you know the function is in the function namespace you need to call #'symbol instead of symbol.
I've done (&rest functions) instead of functions in the prototype that with bad usage (not a list) you get a compile time error and it is more preciese.

What does gensym do in Lisp?

contextualization: I've been doing a university project in which I have to write a parser for regular expressions and build the corresponding epsilon-NFA. I have to do this in Prolog and Lisp.
I don't know if questions like this are allowed, if not I apologize.
I heard some of my classmates talking about how they used the function gensym for that, I asked them what it did and even checked up online but I literally can't understand what this function does neither why or when is best to use it.
In particular, I'm more intrested in what it does in Lisp.
Thank you all.
GENSYM creates unique symbols. Each call creates a new symbol. The symbol usually has a name which includes a number, which is counted up. The name is also unique (the symbol itself is already unique) with a number, so that a human reader can identify different uninterned symbols in the source code.
CL-USER 39 > (gensym)
#:G1083
CL-USER 40 > (gensym)
#:G1084
CL-USER 41 > (gensym)
#:G1085
CL-USER 42 > (gensym)
#:G1086
gensym is often used in Lisp macros for code generation, when the macro needs to create new identifiers, which then don't clash with existing identifiers.
Example: we are going to double the result of a Lisp form and we are making sure that the Lisp form itself will be computed only once. We do that by saving the value in a local variable. The identifier for the local variable will be computed by gensym.
CL-USER 43 > (defmacro double-it (it)
(let ((new-identifier (gensym)))
`(let ((,new-identifier ,it))
(+ ,new-identifier ,new-identifier))))
DOUBLE-IT
CL-USER 44 > (macroexpand-1 '(double-it (cos 1.4)))
(LET ((#:G1091 (COS 1.4)))
(+ #:G1091 #:G1091))
T
CL-USER 45 > (double-it (cos 1.4))
0.33993432
a little clarification of the existing answers (as the op is not yet aware of the typical common lisp macros workflow):
consider the macro double-it, proposed by mr. Joswig. Why would we bother creating this whole bunch of let? when it can be simply:
(defmacro double-it (it)
`(+ ,it ,it))
and ok, it seems to be working:
CL-USER> (double-it 1)
;;=> 2
but look at this, we want to increment x and double it
CL-USER> (let ((x 1))
(double-it (incf x)))
;;=> 5
;; WHAT? it should be 4!
the reason can be seen in macro expansion:
(let ((x 1))
(+ (setq x (+ 1 x)) (setq x (+ 1 x))))
you see, as the macro doesn't evaluate form, just splices it into generated code, it leads to incf being executed twice.
the simple solution is to bind it somewhere, and then double the result:
(defmacro double-it (it)
`(let ((x ,it))
(+ x x)))
CL-USER> (let ((x 1))
(double-it (incf x)))
;;=> 4
;; NICE!
it seems to be ok now. really it expands like this:
(let ((x 1))
(let ((x (setq x (+ 1 x))))
(+ x x)))
ok, so what about the gensym thing?
let's say, you want to print some message, before doubling your value:
(defmacro double-it (it)
`(let* ((v "DOUBLING IT")
(val ,it))
(princ v)
(+ val val)))
CL-USER> (let ((x 1))
(double-it (incf x)))
;;=> DOUBLING IT
;;=> 4
;; still ok!
but what if you accidentally name value v instead of x:
CL-USER> (let ((v 1))
(double-it (incf v)))
;;Value of V in (+ 1 V) is "DOUBLING IT", not a NUMBER.
;; [Condition of type SIMPLE-TYPE-ERROR]
It throws this weird error! Look at the expansion:
(let ((v 1))
(let* ((v "DOUBLING IT") (val (setq v (+ 1 v))))
(princ v)
(+ val val)))
it shadows the v from the outer scope with string, and when you are trying to add 1, well it obviously can't. Too bad.
another example, say you want to call the function twice, and return 2 results as a list:
(defmacro two-funcalls (f v)
`(let ((x ,f))
(list (funcall x ,v) (funcall x ,v))))
CL-USER> (let ((y 10))
(two-funcalls (lambda (z) z) y))
;;=> (10 10)
;; OK
CL-USER> (let ((x 10))
(two-funcalls (lambda (z) z) x))
;; (#<FUNCTION (LAMBDA (Z)) {52D2D4AB}> #<FUNCTION (LAMBDA (Z)) {52D2D4AB}>)
;; NOT OK!
this class of bugs is very nasty, since you can't easily say what's happened.
What is the solution? Obviously not to name the value v inside macro. You need to generate some sophisticated name that no one would reproduce in their code, like my-super-unique-value-identifier-2019-12-27. This would probably save you, but still you can't really be sure. That's why gensym is there:
(defmacro two-funcalls (f v)
(let ((fname (gensym)))
`(let ((,fname ,f))
(list (funcall ,fname ,v) (funcall ,fname ,v)))))
expanding to:
(let ((y 10))
(let ((#:g654 (lambda (z) z)))
(list (funcall #:g654 y) (funcall #:g654 y))))
you just generate the var name for the generated code, it is guaranteed to be unique (meaning no two gensym calls would generate the same name for the runtime session),
(loop repeat 3 collect (gensym))
;;=> (#:G645 #:G646 #:G647)
it still can potentially be clashed with user var somehow, but everybody knows about the naming and doesn't call the var #:GXXXX, so you can consider it to be impossible. You can further secure it, adding prefix
(loop repeat 3 collect (gensym "MY_GUID"))
;;=> (#:MY_GUID651 #:MY_GUID652 #:MY_GUID653)
GENSYM will generate a new symbol at each call. It will be garanteed, that the symbol did not exist before it will be generated and that it will never be generated again. You may specify a symbols prefix, if you like:
CL-USER> (gensym)
#:G736
CL-USER> (gensym "SOMETHING")
#:SOMETHING737
The most common use of GENSYM is generating names for items to avoid name clashes in macro expansion.
Another common purpose is the generaton of symbols for the construction of graphs, if the only thing demand you have is to attach a property list to them, while the name of the node is not of interest.
I think, the task of NFA-generation could make good use of the second purpose.
This is a note to some of the other answers, which I think are fine. While gensym is the traditional way of making new symbols, in fact there is another way which works perfectly well and is often better I find: make-symbol:
make-symbol creates and returns a fresh, uninterned symbol whose name is the given name. The new-symbol is neither bound nor fbound and has a null property list.
So, the nice thing about make-symbol is it makes a symbol with the name you asked for, exactly, without any weird numerical suffix. This can be helpful when writing macros because it makes the macroexpansion more readable. Consider this simple list-collection macro:
(defmacro collecting (&body forms)
(let ((resultsn (make-symbol "RESULTS"))
(rtailn (make-symbol "RTAIL")))
`(let ((,resultsn '())
(,rtailn nil))
(flet ((collect (it)
(let ((new (list it)))
(if (null ,rtailn)
(setf ,resultsn new
,rtailn new)
(setf (cdr ,rtailn) new
,rtailn new)))
it))
,#forms
,resultsn))))
This needs two bindings which the body can't refer to, for the results, and the last cons of the results. It also introduces a function in a way which is intentionally 'unhygienic': inside collecting, collect means 'collect something'.
So now
> (collecting (collect 1) (collect 2) 3)
(1 2)
as we want, and we can look at the macroexpansion to see that the introduced bindings have names which make some kind of sense:
> (macroexpand '(collecting (collect 1)))
(let ((#:results 'nil) (#:rtail nil))
(flet ((collect (it)
(let ((new (list it)))
(if (null #:rtail)
(setf #:results new #:rtail new)
(setf (cdr #:rtail) new #:rtail new)))
it))
(collect 1)
#:results))
t
And we can persuade the Lisp printer to tell us that in fact all these uninterned symbols are the same:
> (let ((*print-circle* t))
(pprint (macroexpand '(collecting (collect 1)))))
(let ((#2=#:results 'nil) (#1=#:rtail nil))
(flet ((collect (it)
(let ((new (list it)))
(if (null #1#)
(setf #2# new #1# new)
(setf (cdr #1#) new #1# new)))
it))
(collect 1)
#2#))
So, for writing macros I generally find make-symbol more useful than gensym. For writing things where I just need a symbol as an object, such as naming a node in some structure, then gensym is probably more useful. Finally note that gensym can be implemented in terms of make-symbol:
(defun my-gensym (&optional (thing "G"))
;; I think this is GENSYM
(check-type thing (or string (integer 0)))
(let ((prefix (typecase thing
(string thing)
(t "G")))
(count (typecase thing
((integer 0) thing)
(t (prog1 *gensym-counter*
(incf *gensym-counter*))))))
(make-symbol (format nil "~A~D" prefix count))))
(This may be buggy.)

Macros That Write Macros - Compile Error

When I compile the following code, SBCL complains that g!-unit-value and g!-unit are undefined. I'm not sure how to debug this. As far as I can tell, flatten is failing.
When flatten reaches the unquoted part of defunits, it seems like the entire part is being treated as an atom. Does that sound correct?
The following uses code from the book Let over Lambda:
Paul Graham Utilities
(defun symb (&rest args)
(values (intern (apply #'mkstr args))))
(defun mkstr (&rest args)
(with-output-to-string (s)
(dolist (a args) (princ a s))))
(defun group (source n)
(if (zerop n) (error "zero length"))
(labels ((rec (source acc)
(let ((rest (nthcdr n source)))
(if (consp rest)
(rec rest (cons (subseq source 0 n) acc))
(nreverse (cons source acc))))))
(if source (rec source nil) nil)))
(defun flatten (x)
(labels ((rec (x acc)
(cond ((null x) acc)
((atom x) (cons x acc))
(t (rec (car x) (rec (cdr x) acc))))))
(rec x nil)))
Let Over Lambda Utilities - Chapter 3
(defmacro defmacro/g! (name args &rest body)
(let ((g!-symbols (remove-duplicates
(remove-if-not #'g!-symbol-p
(flatten body)))))
`(defmacro ,name ,args
(let ,(mapcar
(lambda (g!-symbol)
`(,g!-symbol (gensym ,(subseq
(symbol-name g!-symbol)
2))))
g!-symbols)
,#body))))
(defun g!-symbol-p (symbol-to-test)
(and (symbolp symbol-to-test)
(> (length (symbol-name symbol-to-test)) 2)
(string= (symbol-name symbol-to-test)
"G!"
:start1 0
:end1 2)))
(defmacro defmacro! (name args &rest body)
(let* ((o!-symbols (remove-if-not #'o!-symbol-p args))
(g!-symbols (mapcar #'o!-symbol-to-g!-symbol o!-symbols)))
`(defmacro/g! ,name ,args
`(let ,(mapcar #'list (list ,#g!-symbols) (list ,#o!-symbols))
,(progn ,#body)))))
(defun o!-symbol-p (symbol-to-test)
(and (symbolp symbol-to-test)
(> (length (symbol-name symbol-to-test)) 2)
(string= (symbol-name symbol-to-test)
"O!"
:start1 0
:end1 2)))
(defun o!-symbol-to-g!-symbol (o!-symbol)
(symb "G!" (subseq (symbol-name o!-symbol) 2)))
Let Over Lambda - Chapter 5
(defun defunits-chaining (u units prev)
(if (member u prev)
(error "~{ ~a~^ depends on~}"
(cons u prev)))
(let ((spec (find u units :key #'car)))
(if (null spec)
(error "Unknown unit ~a" u)
(let ((chain (second spec)))
(if (listp chain)
(* (car chain)
(defunits-chaining
(second chain)
units
(cons u prev)))
chain)))))
(defmacro! defunits (quantity base-unit &rest units)
`(defmacro ,(symb 'unit-of- quantity)
(,g!-unit-value ,g!-unit)
`(* ,,g!-unit-value
,(case ,g!-unit
((,base-unit) 1)
,#(mapcar (lambda (x)
`((,(car x))
,(defunits-chaining
(car x)
(cons
`(,base-unit 1)
(group units 2))
nil)))
(group units 2))))))
This is kind of tricky:
Problem: you assume that backquote/comma expressions are plain lists.
You need to ask yourself this question:
What is the representation of a backquote/comma expression?
Is it a list?
Actually the full representation is unspecified. See here: CLHS: Section 2.4.6.1 Notes about Backquote
We are using SBCL. See this:
* (setf *print-pretty* nil)
NIL
* '`(a ,b)
(SB-INT:QUASIQUOTE (A #S(SB-IMPL::COMMA :EXPR B :KIND 0)))
So a comma expression is represented by a structure of type SB-IMPL::COMMA. The SBCL developers thought that this representation helps when such backquote lists need to be printed by the pretty printer.
Since your flatten treats structures as atoms, it won't look inside...
But this is the specific representation of SBCL. Clozure CL does something else and LispWorks again does something else.
Clozure CL:
? '`(a ,b)
(LIST* 'A (LIST B))
LispWorks:
CL-USER 87 > '`(a ,b)
(SYSTEM::BQ-LIST (QUOTE A) B)
Debugging
Since you found out that somehow flatten was involved, the next debugging steps are:
First: trace the function flatten and see with which data it is called and what it returns.
Since we are not sure what the data actually is, one can INSPECT it.
A debugging example using SBCL:
* (defun flatten (x)
(inspect x)
(labels ((rec (x acc)
(cond ((null x) acc)
((atom x) (cons x acc))
(t (rec (car x) (rec (cdr x) acc))))))
(rec x nil)))
STYLE-WARNING: redefining COMMON-LISP-USER::FLATTEN in DEFUN
FLATTEN
Above calls INSPECT on the argument data. In Common Lisp, the Inspector usually is something where one can interactively inspect data structures.
As an example we are calling flatten with a backquote expression:
* (flatten '`(a ,b))
The object is a proper list of length 2.
0. 0: SB-INT:QUASIQUOTE
1. 1: (A ,B)
We are in the interactive Inspector. The commands now available:
> help
help for INSPECT:
Q, E - Quit the inspector.
<integer> - Inspect the numbered slot.
R - Redisplay current inspected object.
U - Move upward/backward to previous inspected object.
?, H, Help - Show this help.
<other> - Evaluate the input as an expression.
Within the inspector, the special variable SB-EXT:*INSPECTED* is bound
to the current inspected object, so that it can be referred to in
evaluated expressions.
So the command 1 walks into the data structure, here a list.
> 1
The object is a proper list of length 2.
0. 0: A
1. 1: ,B
Walk in further:
> 1
The object is a STRUCTURE-OBJECT of type SB-IMPL::COMMA.
0. EXPR: B
1. KIND: 0
Here the Inspector tells us that the object is a structure of a certain type. That's what we wanted to know.
We now leave the Inspector using the command q and the flatten function continues and returns a value:
> q
(SB-INT:QUASIQUOTE A ,B)
For anyone else who is trying to get defmacro! to work on SBCL, a temporary solution to this problem is to grope inside the unquote structure during the flatten procedure recursively flatten its contents:
(defun flatten (x)
(labels ((flatten-recursively (x flattening-list)
(cond ((null x) flattening-list)
((eq (type-of x) 'SB-IMPL::COMMA) (flatten-recursively (sb-impl::comma-expr x) flattening-list))
((atom x) (cons x flattening-list))
(t (flatten-recursively (car x) (flatten-recursively (cdr x) flattening-list))))))
(flatten-recursively x nil)))
But this is horribly platform dependant. If I find a better way, I'll post it.
In case anyone's still interested in this one, here are my three cents. My objection to the above modification of flatten is that it might be more naturally useful as it were originally, while the problem with representations of unquote is rather endemic to defmacro/g!. I came up with a not-too-pretty modification of defmacro/g! using features to decide what to do. Namely, when dealing with non-SBCL implementations (#-sbcl) we proceed as before, while in the case of SBCL (#+sbcl) we dig into the sb-impl::comma structure, use its expr attribute when necessary and use equalp in remove-duplicates, as we are now dealing with structures, not symbols. Here's the code:
(defmacro defmacro/g! (name args &rest body)
(let ((syms (remove-duplicates
(remove-if-not #-sbcl #'g!-symbol-p
#+sbcl #'(lambda (s)
(and (sb-impl::comma-p s)
(g!-symbol-p (sb-impl::comma-expr s))))
(flatten body))
:test #-sbcl #'eql #+sbcl #'equalp)))
`(defmacro ,name ,args
(let ,(mapcar
(lambda (s)
`(#-sbcl ,s #+sbcl ,(sb-impl::comma-expr s)
(gensym ,(subseq
#-sbcl
(symbol-name s)
#+sbcl
(symbol-name (sb-impl::comma-expr s))
2))))
syms)
,#body))))
It works with SBCL. I have yet to test it thoroughly on other implementations.

Reading Outer Nested Forms in Lisp?

Is there a way to do this:
(let ((x 5)(y 7))
(get-outer-form) ;; 'get-outer-form would capture the entire LET expression
(* x y))
35 ;; value returned from LET
*current-form-value* ;; variable to hold the form
(let ((x 5))(y 7))(* x y)) ;; value of evaluating *current-form-value*
If it can be done, pseudo-code will suffice. I'll naively assume that this would have to be done with read, however, if there is too much overhead generated from doing this, I will have to find another solution. Thanks.
No its not possible by default. Doing so would need some advanced code and is not likely to work easily:
custom evaluator
code walker which injects the necessary code
I've been fiddling a little around and came up with this. It's not exactly what you want but it's close. It it were possible to rename let and make your own it would be exactly what you want.
(defmacro letc (p &body b)
(when (equal (car b) '(get-outer-form))
(setq b `((setf *current-form-value* '(let ,p ,#(cdr b))),#(cdr b))))
`(let ,p ,#b))
(letc ((x 5)(y 7))
(get-outer-form) ;; 'get-outer-form would capture the entire LET expression
(* x y))
;; ==> 35
*current-form-value*
;; ==> (let ((x 5) (y 7)) (* x y))
Or simpler. Using letc implies you want it captured.
(defmacro letc (p &body b)
`(let ,p (setf *current-form-value* '(letc ,p ,#b)),#b)))
(letc ((x 5)(y 7))
(* x y))
;; ==> 35
*current-form-value*
;; ==> (letc ((x 5) (y 7)) (* x y))
Both of them have problems with nesting:
(letc ((x 5)(y 7))
(letc ((a (+ x y)))
(* 2 a)))
;; ==> 24
*current-form-value*
;; ==> (let ((a (+ x y))) (* 2 a))
I think Rainer is basically correct, but I couldn't help trying for a subset of your goal with either *macroexpand-hook* or a reader approach. I don't bother removing (get-outer-form) from the current form in either case, but that should be straightforward list manipulation.
First a reader approach. Wrap the open parenthesis reader with a function that searches for (get-outer-form) within the result of calling the default open parenthesis reader.
;(in-package |cl-user|)
(defparameter *standard-readtable* (copy-readtable ()))
*STANDARD-READTABLE*
;(in-package |cl-user|)
(defvar *current-form-value* ())
*CURRENT-FORM-VALUE*
;(in-package |cl-user|)
(defun get-outer-form ()
())
GET-OUTER-FORM
;(in-package |cl-user|)
(defun get-outer-form-paren-reader (stream char &optional count)
(declare (ignore count))
(let* ((seen ())
(paren-reader
(get-macro-character #\( *standard-readtable*))
(form (funcall paren-reader stream char)))
(subst-if ()
(lambda (x)
;; never substitute, search only.
(prog1 ()
(when (equalp x '(get-outer-form))
(setq seen t))))
form)
(when seen
(setq *current-form-value* form))
form))
GET-OUTER-FORM-PAREN-READER
;(in-package |cl-user|)
(set-macro-character #\( #'get-outer-form-paren-reader)
T
Second, a *macroexpand-hook* approach. Look for (get-outer-form) in forms before they are macroexpanded.
;(in-package |cl-user|)
(defun get-outer-form ()
(error "get-outer-form only works from within a macro"))
GET-OUTER-FORM
;(in-package |cl-user|)
(defvar *current-form-value* ())
*CURRENT-FORM-VALUE*
;(in-package |cl-user|)
(defun mhook (expander form env)
(let* ((seen ())
(fixed (subst-if ()
(lambda (x)
(when (equalp x '(get-outer-form))
(setq seen t)))
form)))
(when seen (setq *current-form-value* form))
(funcall expander fixed env)))
MHOOK
;(in-package |cl-user|)
(setq *macroexpand-hook* #'mhook)
#<Compiled-function MHOOK #x30200FC5BB1F>

Increment several variables at once, using &rest?

I would like to create a function that allows to:
(incf vara varb varc vard)
Instead of
(incf vara)
(incf varb)
(incf varc)
(incf vard)
What I do not understand is how to be able to send more arguments, how to define that in a function?
(defun inc (&rest arg)
(interactive)
(mapcar 'incf arg)
)
This increases the argument, but ofcourse does not save them back into the variables.
How to go about this?
If you want to be able to write this form as (my-incf a b c) without quoting the variable names a, b, and c, make it a macro rather than a function:
(defmacro incf+ (&rest vars)
`(progn
,#(mapcar (lambda (var) `(incf ,var)) vars)))
Check that it expands into the right code using macroexpand:
(macroexpand '(incf+ var1 var2 var3))
;; => (progn (incf var1) (incf var2) (incf var3))
Because variables in Emacs Lisp have dynamic scope by default, you can accomplish almost the same thing with a function which takes quoted variable names as arguments. But the macro version has the advantage that, since it expands into code in the place when it was called, it will work with lexically bound variables as well. symbol-value only works with dynamically bound variables.
You can test this by putting the following in a file and loading it (in Emacs 24 or higher):
;; -*- lexical-binding: t -*-
(defun incf+fun (&rest vars)
(mapc #'(lambda (var) (incf (symbol-value var))) vars))
(defun incf-macro-test ()
(let ((a 5) (b 7) (c 11))
(incf+ a b c)
(list a b c)))
(defun incf-function-test ()
(let ((a 5) (b 7) (c 11))
(incf+fun 'a 'b 'c)
(list a b c)))
Evaluating (incf-macro-test) will return (6 8 12), but (incf-function-test) will enter the debugger with a (void-variable a) error.
It should work:
(require 'cl)
(setq a 1)
(setq b 2)
(defun inc (&rest arg)
(interactive)
(mapc (lambda (x) (incf (symbol-value x))) arg))
(inc 'a 'b)
(message "%s %s" a b) => (2 3)
You have to quote each argument otherwise (inc a b) becomes (inc 1 2) before executing inc.