Using the `once-only` macro - macros

At the end of Ch 8 in Practical Common Lisp, Peter Seibel presents the once-only macro. Its purpose is to mitigate a number of subtle problems with variable evaluation in user-defined macros. Note I'm not trying to understand at this point how this macro works, as in some other posts, but just how to use it properly:
(defmacro once-only ((&rest names) &body body)
(let ((gensyms (loop for n in names collect (gensym))))
`(let (,#(loop for g in gensyms collect `(,g (gensym))))
`(let (,,#(loop for g in gensyms for n in names collect ``(,,g ,,n)))
,(let (,#(loop for n in names for g in gensyms collect `(,n ,g)))
,#body)))))
The following is a sample (incorrect) contrived macro that attempts to exhibit several variable evaluation problems. It purports to iterate over a range of integers by some delta, returning the range:
(defmacro do-range ((var start stop delta) &body body)
"Sample macro with faulty variable evaluations."
`(do ((,var ,start (+ ,var ,delta))
(limit ,stop))
((> ,var limit) (- ,stop ,start))
,#body))
For example, (do-range (i 1 15 3) (format t "~A " i)) should print 1 4 7 10 13 and then return 14.
The problems include 1) potential capture of the second occurrence of limit, since it occurs as a free variable, 2) potential capture of the initial occurrence of the bound variable limit, since it occurs in an expression along with other variables appearing in the macro parameters, 3) out of order evaluation, since delta will be evaluated before stop, even though stop appears before delta in the parameter list, and 4) multiple variable evaluations, since stop and start are evaluated more than once. As I understand it, once-only should fix these problems:
(defmacro do-range ((var start stop delta) &body body)
(once-only (start stop delta limit)
`(do ((,var ,start (+ ,var ,delta))
(limit ,stop))
((> ,var limit) (- ,stop ,start))
,#body)))
However, (macroexpand '(do-range (i 1 15 3) (format t "~A " i))) complains about limit being an unbound variable. If I switch instead to with-gensyms, which should take care of problems 1 & 2 above only, the expansion proceeds without incident.
Is this an issue with the once-only macro? And does once-only really solve all the problems outlined above (and perhaps others)?

The ONCE-ONLY macro
To get rid of a warning that N is unused, I would change the macro to:
(defmacro once-only ((&rest names) &body body)
(let ((gensyms (loop for nil in names collect (gensym))))
; changed N to NIL, NIL is ignored
`(let (,#(loop for g in gensyms collect `(,g (gensym))))
`(let (,,#(loop for g in gensyms for n in names collect ``(,,g ,,n)))
,(let (,#(loop for n in names for g in gensyms collect `(,n ,g)))
,#body)))))
The purpose of this macro is to make sure that expressions are only evaluated once and in a defined order. For that it will introduce new uninterned variables and will bind the evaluation results to those. Inside he macro the new variables are available. The macro itself is provided to make writing macros easier.
Using ONCE-ONLY in DO-RANGE
Your example use of ONCE-ONLY:
(defmacro do-range ((var start stop delta) &body body)
(once-only (start stop delta limit)
`(do ((,var ,start (+ ,var ,delta))
(limit ,stop))
((> ,var limit) (- ,stop ,start))
,#body)))
Why is there LIMIT in the once-only list? limit is undefined there. LIMIT is used inside the ONCE-ONLY form as a symbol, but outside there is no binding.
ONCE-ONLY expects that the list of names is a list of symbols and that these names are bound to forms. In your case limit is a symbol, but it is undefined.
We need to remove limit from the list of names:
(defmacro do-range ((var start stop delta) &body body)
(once-only (start stop delta)
`(do ((,var ,start (+ ,var ,delta))
(limit ,stop))
((> ,var limit) (- ,stop ,start))
,#body)))
Now, what to do about LIMIT? Given that once-only provides bindings for the names, including for STOP, we can eliminate the symbol LIMIT and replace its use with ,stop:
(defmacro do-range ((var start stop delta) &body body)
(once-only (start stop delta)
`(do ((,var ,start (+ ,var ,delta)))
((> ,var ,stop) (- ,stop ,start))
,#body)))
Example:
CL-USER 137 > (pprint
(macroexpand
'(do-range (i 4 10 2)
(print i))))
(LET ((#1=#:G2170 4)
(#3=#:G2171 10)
(#2=#:G2172 2))
(DO ((I #1# (+ I #2#)))
((> I #3#) (- #3# #1#))
(PRINT I)))

Related

Lisp - Passing unquoted list to macro

I'm currently experimenting with macro's in Lisp and I would like to write a macro which can handle syntax as follows:
(my-macro (args1) (args2))
The macro should take two lists which would then be available within my macro to do further processing. The catch, however, is that the lists are unquoted to mimic the syntax of some real Lisp/CLOS functions. Is this possible?
Currently I get the following error when attempting to do something like this:
Undefined function ARGS1 called with arguments ().
Thanks in advance!
I think you need to show what you have tried to do. Here is an example of a (silly) macro which has an argument pattern pretty much what yours is:
(defmacro stupid-let ((&rest vars) (&rest values) &body forms)
;; Like LET but with a terrible syntax
(unless (= (length vars) (length values))
(error "need exactly one value for each variable"))
(unless (every #'symbolp vars)
(error "not every variable is a symbol"))
`(let ,(mapcar #'list vars values) ,#forms))
Then
> (macroexpand '(stupid-let (a b c) (1 2 3) (+ a b c)))
(let ((a 1) (b 2) (c 3)) (+ a b c))
The above macro depends on defmacro's arglist-destructuring, but you don't have to do that:
(defun proper-list-p (l)
;; elaborate version with an occurs check, quadratic.
(labels ((plp (tail tails)
(if (member tail tails)
nil
(typecase tail
(null t)
(cons (plp (rest tail) (cons tail tails)))
(t nil)))))
(plp l '())))
(defmacro stupid-let (vars values &body forms)
;; Like LET but with a terrible syntax
(unless (and (proper-list-p vars) (proper-list-p values))
(error "need lists of variables and values"))
(unless (= (length vars) (length values))
(error "need exactly one value for each variable"))
(unless (every #'symbolp vars)
(error "not every variable is a symbol"))
`(let ,(mapcar #'list vars values) ,#forms))
As a slightly more useful example, here is a macro which is a bit like the CLOS with-slots / with-accessors macros:
(defmacro with-mindless-accessors ((&rest accessor-specifications) thing
&body forms)
"Use SYMBOL-MACROLET to define mindless accessors for THING.
Each accessor specification is either a symbol which names the symbol
macro and the accessor, or a list (macroname accessorname) which binds
macroname to a symbol macro which calls accessornam. THING is
evaluated once only."
(multiple-value-bind (accessors functions)
(loop for accessor-specification in accessor-specifications
if (symbolp accessor-specification)
collect accessor-specification into acs
and collect accessor-specification into fns
else if (and (proper-list-p accessor-specification)
(= (length accessor-specification) 2)
(every #'symbolp accessor-specification))
collect (first accessor-specification) into acs
and collect (second accessor-specification) into fns
else do (error "bad accessor specification ~A" accessor-specification)
end
finally (return (values acs fns)))
(let ((thingn (make-symbol "THING")))
`(let ((,thingn ,thing))
(symbol-macrolet ,(loop for accessor in accessors
for function in functions
collect `(,accessor (,function ,thingn)))
,#forms)))))
So now we can write this somewhat useless code:
> (with-mindless-accessors (car cdr) (cons 1 2)
(setf cdr 3)
(+ car cdr))
4
And this:
> (let ((l (list 1 2)))
(with-mindless-accessors (second) l
(setf second 4)
l))
(1 4)

What is the best way of combining &key and &rest in a lisp macro's lambda list?

I implemented Heap's algorithm using a macro. It's working OK, but I would like to tweak it so it will generate anaphoric or non-anaphoric code on demand. In other words, I would like to have the macro either make an internal copy of the sequence it will permutate or work on a sequence available outside the macro.
My utterly unsatisfactory, downright embarrassing code is:
;; Anaphoric version
;; To make it non-anaphoric, substitute (,var (copy-seq ,vec)) for (,var ,vec)
(defmacro run-permutations (var vec &rest body)
"Executes body for all permutations of vec, which is stored in variable var"
`(let ((,var ,vec))
(labels ((generate (&optional (n (length ,var)))
(if (= n 1)
(progn ,#body)
(progn
(loop for i from 0 below (1- n)
do (progn
(generate (1- n))
(rotatef (aref ,var (if (evenp n) i 0))
(aref ,var (1- n)))))
(generate (1- n))))))
(generate))))
? (run-permutations v "123" (pprint v))
"123"
"213"
"312"
"132"
"231"
"321"
?
I would like to write something that worked like this...
? (setf v "123")
? (run-permutations :anaphoric t v "123" (...do stuff...))
? v
"321"
? (setf v "123")
? (run-permutations v "123" (...do stuff...))
? v
"123"
...but I haven't found a satisfactory combination of &rest and &key or any other approach for writing the lambda list.
So my question is: is there a way of accomplishing that, preferably without writing more code to parse the macro's lambda list? Or is there another, more or less standard (and presumably more elegant) solution out there? I strongly suspect the latter.
Your input is much appreciated. As always, any other comments on the code are appreciated as well.
UPDATE
Brilliant! I opted to use a gensym for n because body is called from within the recursion and I can't see how it could be called from elsewhere—at least not without rewriting everything.
I've also added another feature and a minor optimization. In case you're curious, the updated version is:
(defmacro do-permutations ((var vec &key anaphoric (len (length vec))) &body body)
"Executes body for all permutations of vec, which is stored in variable var.
KEYS:
anaphoric: if defined, modifies var outside the macro, preserves it otherwise
len: number of items that will be permuted, default is the full vector"
(let ((n (gensym)))
`(let ((,var ,(if anaphoric vec `(copy-seq ,vec))))
(labels ((generate (&optional (,n ,len))
(if (= ,n 1)
(progn ,#body)
(let ((n-1 (1- ,n)))
(loop for i from 0 below n-1
do (progn
(generate n-1)
(rotatef (aref ,var (if (evenp ,n) i 0))
(aref ,var n-1))))
(generate n-1)))))
(generate)))))
Finally, I tried to remove theprogn after do but it didn't work because 2 expressions have to be evaluated at that point.
Indent your code correctly:
(defmacro run-permutations (var vec &rest body)
"Executes body for all permutations of vec, which is stored in variable var"
`(let ((,var ,vec))
(labels ((generate (&optional (n (length ,var)))
(if (= n 1)
(progn ,#body)
(progn
(loop for i from 0 below (1- n)
do (progn
(generate (1- n))
(rotatef (aref ,var (if (evenp n) i 0))
(aref ,var (1- n)))))
(generate (1- n))))))
(generate))))
Use something like:
(do-permutations (v "123" :anaphoric t)
(some)
(stuff))
with a macro:
(defmacro do-permutations ((var vec &key anaphoric) &body body)
...)
other names: doing-permutations, with-permutations, ...
Note also that the body can be declared with &body, instead of &rest. The semantics is the same, but one expect it to be indented differently. &body signals that a list of Lisp forms follows.
You also don't need a progn in a loopafter do.
The body sees the variable n. You may think of another place for the body...

Lisp: defmacro with &optional and &body

I wrote a quick and dirty macro to time lisp code. However, the problem I am facing now is that I wanted to include an optional output-stream in the function. However, I can not figure out how to use both the &optional and &body parameters in the defmacro. I looked for examples but found only those for defun which I think I understand. I am not able to figure out why this is failing for me. Any hints:
(defmacro timeit (&optional (out-stream *standard-output*) (runs 1) &body body)
"Note that this function may barf if you are depending on a single evaluation
and choose runs to be greater than one. But I guess that will be the
caller's mistake instead."
(let ((start-time (gensym))
(stop-time (gensym))
(temp (gensym))
(retval (gensym)))
`(let ((,start-time (get-internal-run-time))
(,retval (let ((,temp))
(dotimes (i ,runs ,temp)
(setf ,temp ,#body))))
(,stop-time (get-internal-run-time)))
(format ,out-stream
"~CTime spent in expression over ~:d iterations: ~f seconds.~C"
#\linefeed ,runs
(/ (- ,stop-time ,start-time)
internal-time-units-per-second)
#\linefeed)
,retval)))
This is how I intend to use the code:
(timeit (+ 1 1)) ; Vanilla call
(timeit *standard-output* (+ 1 1)) ; Log the output to stdout
(timeit *standard-output* 1000 (+ 1 1)) ; Time over a 1000 iterations.
I think this, found from the hyperspec, on defmacro is a similar idea.
(defmacro mac2 (&optional (a 2 b) (c 3 d) &rest x) `'(,a ,b ,c ,d ,x)) => MAC2
(mac2 6) => (6 T 3 NIL NIL)
(mac2 6 3 8) => (6 T 3 T (8))
EDIT: Keyword arguments
The usage shown above is clearly flawed. Perhaps, this is better:
(timeit (+ 1 1)) ; Vanilla call
(timeit :out-stream *standard-output* (+ 1 1)) ; Log the output to stdout
(timeit :out-stream *standard-output* :runs 1000 (+ 1 1)) ; Time over a 1000 iterations.
Thanks.
How should that work?
How should it be detected that the first thing is the optional stream?
(timeit a) ; is a the optional stream or an expression to time?
(timeit a b) ; is a the optional stream or an expression to time?
(timeit a b c) ; is a the optional stream or an expression to time?
I would avoid such macro arglists.
Usually I would prefer:
(with-timings ()
a b c)
and with a stream
(with-timings (*standard-output*)
a b c)
The first list gives the optional parameters. The list itself is not optional.
That macro should be easier to write.
Generally it may not be necessary to specify a stream:
(let ((*standard-output* some-stream))
(timeit a b c))
You can implement what you want, but I would not do it:
(defmacro timeit (&rest args)
(case (length args)
(0 ...)
(1 ...)
(otherwise (destructuring-bind (stream &rest body) ...))))
Solution: With a non-optional keyword arglist
(defmacro timeit ((&key
(to-stream *standard-output*)
(with-runs 1))
&body body)
"Note that this function may barf if you are depending on a single evaluation
and choose with-runs to be greater than one. But I guess that will be the
caller's mistake instead."
(let ((start-time (gensym))
(stop-time (gensym))
(temp (gensym))
(retval (gensym))
(elapsed-time (gensym)))
`(let* ((,start-time (get-internal-run-time))
(,retval (let ((,temp))
(dotimes (i ,with-runs ,temp)
(setf ,temp ,#body))))
(,stop-time (get-internal-run-time))
(,elapsed-time (/ (- ,stop-time ,start-time)
internal-time-units-per-second)))
(format ,to-stream
(concatenate 'string
"~CAverage (total) time spent in expression"
" over ~:d iterations: ~f (~f) seconds.~C")
#\linefeed
,with-runs
,elapsed-time
(/ ,elapsed-time ,with-runs)
#\linefeed)
,retval)))
Based on Rainer's comments.
Usage pattern:
(timeit nil (+ 1 1)) ; Vanilla case
(timeit (:to-stream *standard-output*) (+ 1 1)) ; Log to stdout
(timeit (:with-runs 1000) (+ 1 1)) ; Evaluate 1000 times
(timeit (:with-runs 1000 :to-stream *standard-output*) (+ 1 1)) ; Evaluate 1000 times and log to stdout
I've of the general opinion that these kind of arguments should generally be provided in a separate list that is the first argument to the macro. This is especially common in the with- type macros. Some other answers have shown how you can do that, but I think it's also a good macro-writing technique to write a functional version first that implements the main functionality, and to then write a macro version. This one isn't too hard, although the approach here does have the potential to add some time increase for function call overhead.
(defun %timeit (function &optional (runs 1) (stream *standard-output*))
(let ((start (get-internal-run-time))
ret
stop)
(prog1 (dotimes (i runs ret)
(declare (ignorable i))
(setf ret (funcall function)))
(setf stop (get-internal-run-time))
(format stream "~&Time spent in ~a iterations: ~f seconds."
runs
(/ (- stop start) internal-time-units-per-second)))))
(defmacro timeit ((&optional (runs 1) (stream *standard-output*)) &body body)
`(%timeit #'(lambda () ,#body) ,runs ,stream))
CL-USER> (timeit (10000000) (1+ most-positive-fixnum))
Time spent in 10000000 iterations: 0.148 seconds.
4611686018427387904

expanding a parameter list in a common lisp macro

I'm trying to teach myself common lisp, and as an exercise in macro-writing, I'm trying to create a a macro to define a nested-do loop of arbitrary depth. I'm working with sbcl, using emacs and slime.
To start, I wrote this double-loop macro:
(defmacro nested-do-2 (ii jj start end &body body)
`(do ((,ii ,start (1+ ,ii)))
((> ,ii ,end))
(do ((,jj ,ii (1+ ,jj)))
((> ,jj ,end))
,#body)))
which I could then use as follows:
(nested-do-2 ii jj 10 20 (print (+ ii jj)))
BTW, I originally wrote this macro using gensym to generate the loop counters (ii, jj), but then I realized that the macro was pretty useless if I couldn't access the counters in the body.
Anyway, I would like to generalize the macro to create a nested-do loop that would be nested to an arbitrary level. This is what I've got so far, but it doesn't quite work:
(defmacro nested-do ((&rest indices) start end &body body)
`(dolist ((index ,indices))
(do ((index ,start (1+ index)))
((> index ,end))
(if (eql index (elt ,indices (elt (reverse ,indices) 0)))
,#body))))
which I would like to invoke as follows:
(nested-do (ii jj kk) 10 15 (print (+ ii jj kk)))
However, the list is not being expanded properly, and I end up in the debugger with this error:
error while parsing arguments to DEFMACRO DOLIST:
invalid number of elements in
((INDEX (II JJ KK)))
And in case it's not obvious, the point of the embedded if statement is to execute the body only in the innermost loop. That doesn't seem terribly elegant to me, and it's not really tested (since I haven't been able to expand the parameter list yet), but it's not really the point of this question.
How can I expand the list properly within the macro? Is the problem in the macro syntax, or in the expression of the list in the function call? Any other comments will also be appreciated.
Thanks in advance.
Here's one way to do it - build the structure from the bottom (loop body) up each index:
(defmacro nested-do ((&rest indices) start end &body body)
(let ((rez `(progn ,#body)))
(dolist (index (reverse indices) rez)
(setf rez
`(do ((,index ,start (1+ ,index)))
((> ,index ,end))
,rez)))))
[Aside from the down votes, this actually works and it is beautiful too!]
Just to clearly illustrate the recursive nature of the macro definition, here is a Scheme implementation:
(define-syntax nested-do
(syntax-rules ()
((_ ((index start end)) body)
(do ((index start (+ 1 index)))
((= index end))
body))
((_ ((index start end) rest ...) body)
(do ((index start (+ 1 index)))
((= index end))
(nested-do (rest ...) body)))))
Using the above, as a template, something like this gets it done:
(defmacro nested-do ((&rest indices) start end &body body)
(let ((index (car indices)))
`(do ((,index ,start (1+ ,index)))
((> ,index ,end))
,(if (null (cdr indices))
`(progn ,#body)
`(nested-do (,#(cdr indices)) ,start ,end ,#body)))))
* (nested-do (i j) 0 2 (print (list i j)))
(0 0)
(0 1)
(0 2)
(1 0)
(1 1)
(1 2)
(2 0)
(2 1)
(2 2)
NIL
Note that with all Common-Lisp macros you'll need to use the 'gensym' patterns to avoid variable capture.

What is wrong with the following Common Lisp macro using gensym?

Learning Common Lisp (using GNU CLISP 2.43) .. so might be a noob mistake. Example is the 'print prime numbers between x and y'
(defun is-prime (n)
(if (< n 2) (return-from is-prime NIL))
(do ((i 2 (1+ i)))
((= i n) T)
(if (= (mod n i) 0)
(return NIL))))
(defun next-prime-after (n)
(do ((i (1+ n) (1+ i)))
((is-prime i) i)))
(defmacro do-primes-v2 ((var start end) &body body)
`(do ((,var (if (is-prime ,start)
,start
(next-prime-after ,start))
(next-prime-after ,var)))
((> ,var ,end))
,#body))
(defmacro do-primes-v3 ((var start end) &body body)
(let ((loop-start (gensym))
(loop-end (gensym)))
`(do ((,loop-start ,start)
(,loop-end ,end)
(,var (if (is-prime ,loop-start)
,loop-start
(next-prime-after ,loop-start))
(next-prime-after ,var)))
((> ,var ,loop-end))
,#body )))
do-primes-v2 works perfectly.
[13]> (do-primes-v2 (p 10 25) (format t "~d " p))
11 13 17 19 23
Next I tried using gensym to avoid naming clashes in macro expansion - do-primes-v3. However I'm stuck with a
*** - EVAL: variable #:G3498 has no value
Tried using macro-expand to see if i could spot the mistake but I can't.
[16]> (macroexpand-1 `(do-primes-v3 (p 10 25) (format t "~d " p)))
(DO
((#:G3502 10) (#:G3503 25)
(P (IF (IS-PRIME #:G3502) #:G3502 (NEXT-PRIME-AFTER #:G3502))
(NEXT-PRIME-AFTER P)))
((> P #:G3503)) (FORMAT T "~d " P)) ;
Use DO* instead of DO.
DO Initializes the bindings in a scope where they are not yet visible. DO* initializes the bindings in a scope where they are visible.
In this particular case var needs to reference the other binding loop-start.
You don't actually need the gensym here for avoiding variable capture, because you do not introduce any variables that would be "local to the macro". When you macroexpand your do-primes-v2, you will see that no variable is introduced that didn't exist outside of the macro.
You do need it for a different thing, though: avoiding multiple evaluation.
If you call the macro like this:
(do-primes-v2 (p (* x 2) (* y 3))
(format "~a~%" p))
it expands to
(do ((p (if (is-prime (* x 2))
(* x 2)
(next-prime-after (* x 2))
(next-prime-after p)))
((> p (* y 3))
(format "~a~%" p))
At best, this is inefficient, because those multiplications are done multiple times. However, if you use a function with side effects as inputs, like setf or incf, this can be a big problem.
Either move the binding of your loop-start and loop-end to an enclosing LET block or use DO*. The reason is that all loop variables in DO are bound "in parallel", so for the first binding, the (expanded) loop-start variable does not yet have a binding.
I know this doesn't really answer your question, but I do think it is relevant. In my experience, the type of macro you are attempting to write is a very common one. One problem I have with the way you have approached the problem is that it doesn't handle another common use case: functional composition.
I don't have the time to highlight some of the difficulties you will probably encounter using your macro, I will however highlight that, had you built your prime iterator geared towards functional composition, your macro turns out to be extremely simple, avoiding your question altogether.
Note: I have slightly modified some of your functions.
(defun is-prime (n)
(cond
((< n 2)
nil)
((= n 2)
t)
((evenp n)
nil)
(t
(do ((i 2 (1+ i)))
((= i n) t)
(when (or (= (mod n i) 0))
(return nil))))))
(defun next-prime (n)
(do ((i n (1+ i)))
((is-prime i) i)))
(defun prime-iterator (start-at)
(let ((current start-at))
(lambda ()
(let ((next-prime (next-prime current)))
(setf current (1+ next-prime))
next-prime))))
(defun map-primes/iterator (fn iterator end)
(do ((i (funcall iterator) (funcall iterator)))
((>= i end) nil)
(funcall fn i)))
(defun map-primes (fn start end)
(let ((iterator (prime-iterator start)))
(map-primes/iterator fn iterator end)))
(defmacro do-primes ((var start end) &body body)
`(map-primes #'(lambda (,var)
,#body)
,start ,end))
I too recommend that you look at Series. The generator pattern is also a very common occurrence in lisp programs. You may also want to look at Alexandria, in particular the function ALEXANDRIA:COMPOSE to see what cool stuff you can do with functional composition.
I suggest avoiding DO/DO* and macros altogether and instead going for Series (an implementation of which can be found on series.sourceforge.net).
If that's too complex then consider just generating a list of primes with recursion or a generator (for on-demand generation).