scheme macro produces unexpected result - macros

Does someone know why the following produces the expected result - (2 4 6)
(defmacro mult2 (lst)
(define (itter x)
(list '* 2 x))
`(list ,#(map itter lst)))
(mult2 (1 2 3))
while I expected that this one would (with the list identifier)
(defmacro mult2 (lst)
(define (itter x)
(list '* 2 x))
`(list ,#(map itter lst)))
(mult2 '(1 2 3))

Macro "arguments" are not evaluated. So, when you pass in '(1 2 3), i.e., (quote (1 2 3)), that is exactly what the macro sees.
P.S. You are much better off using hygienic macros in Scheme. Here's an example using syntax-case:
(define-syntax mult2
(lambda (stx)
(define (double x)
#`(* 2 #,x))
(syntax-case stx ()
((_ lst)
#`(list #,#(map double (syntax-e #'lst)))))))
(That's still not how such a macro is idiomatically written, but I tried to mirror your version as closely as possible.)

That's because the '(1 2 3) is expanded by the reader into (quote (1 2 3)). Since you only destructure one list in your macro, it won't work as expected.
Some general advice: if you're working in Racket you probably want to avoid using defmacro. That is definitely not the idiomatic way to write macros. Take a look at syntax-rules and, if you want to define more complicated macros, syntax-parse. Eli also wrote an article explaining syntax-case for people used to defmacro.

Related

Common Lisp: Destructure a list in first, rest, last (like Python iterable unpacking)

Exercise 6.36 of David Touretzky's Common Lisp book asks for a function swap-first-last that swaps the first and last argument of any list. I feel really stupid right now, but I am unable to solve this with destructuring-bind.
How can I do what in Python would be first, *rest, last = (1,2,3,4) (iterable unpacking) in Common Lisp/with destructuring-bind?
After all trying out, and with some comments by #WillNess (thanks!) I came up with this idea:
macro bind
The idea is trying to subdivide the list and use the &rest functionality of the lambda list in destructuring-bind, however, using the shorter . notation - and using butlast and the car-last combination.
(defmacro bind ((first _rest last) expr &body body)
`(destructuring-bind ((,first . ,_rest) ,last)
`(,,(butlast expr) ,,(car (last expr)))
,#body)))
usage:
(bind (f _rest l) (list 1 2 3 4)
(list f _rest l))
;; => (1 (2 3) 4)
My original answer
There is no so elegant possibility like for Python.
destructuring-bind cannot bind more differently than lambda can: lambda-lists take only the entire rest as &rest <name-for-rest>.
No way there to take the last element out directly.
(Of course, no way, except you write a macro extra for this kind of problems).
(destructuring-bind (first &rest rest) (list 1 2 3 4)
(let* ((last (car (last rest)))
(*rest (butlast rest)))
(list first *rest last)))
;;=> (1 (2 3) 4)
;; or:
(destructuring-bind (first . rest) (list 1 2 3 4)
(let* ((last (car (last rest)))
(*rest (butlast rest)))
(list first *rest last)))
But of course, you are in lisp, you could theoretically write macros to
destructuring-bind in a more sophisticated way ...
But then, destructuring-bind does not lead to much more clarity than:
(defparameter *l* '(1 2 3 4))
(let ((first (car *l*))
(*rest (butlast (cdr *l*)))
(last (car (last *l*))))
(list first *rest last))
;;=> (1 (2 3) 4)
The macro first-*rest-last
To show you, how quickly in common lisp such a macro is generated:
;; first-*rest-last is a macro which destructures list for their
;; first, middle and last elements.
;; I guess more skilled lisp programmers could write you
;; kind of a more generalized `destructuring-bind` with some extra syntax ;; that can distinguish the middle pieces like `*rest` from `&rest rest`.
;; But I don't know reader macros that well yet.
(ql:quickload :alexandria)
(defmacro first-*rest-last ((first *rest last) expr &body body)
(let ((rest))
(alexandria:once-only (rest)
`(destructuring-bind (,first . ,rest) ,expr
(destructuring-bind (,last . ,*rest) (nreverse ,rest)
(let ((,*rest (nreverse ,*rest)))
,#body))))))
;; or an easier definition:
(defmacro first-*rest-last ((first *rest last) expr &body body)
(alexandria:once-only (expr)
`(let ((,first (car ,expr))
(,*rest (butlast (cdr ,expr)))
(,last (car (last ,expr))))
,#body))))
Usage:
;; you give in the list after `first-*rest-last` the name of the variables
;; which should capture the first, middle and last part of your list-giving expression
;; which you then can use in the body.
(first-*rest-last (a b c) (list 1 2 3 4)
(list a b c))
;;=> (1 (2 3) 4)
This macro allows you to give any name for the first, *rest and last part of the list, which you can process further in the body of the macro,
hopefully contributing to more readability in your code.

How to insert literal identifier from input pattern as symbol in syntax-rules macro

I have code like this:
(define-syntax macron
(syntax-rules ()
((_ name)
(lambda (x)
(eval (cons 'name x) (interaction-environment))))))
(define x (map (macron lambda)
'(((x) (display x)) ((a b) (+ a b)))))
(let ((square (car x))
(sum (cadr x)))
(display (square 10))
(newline)
(display (sum 1 2 3))
(newline))
the code is working it use macro as value by wrapping it with lambda. My question is how can I put inside syntax-rule macro literal symbol 'name instead of (cons 'lambda ...) so the output code is:
(lambda (x)
(eval (cons 'name x) (interaction-environment)))
so it work with code like this:
(define (name x)
(display x)
(newline))
(for-each (macron lambda) ;; lambda can be anything
'((1) (2) (3)))
and it print all the numbers.
I know that I can change the name in pattern into something else, but I want to know more about syntax-rules and it's edge cases. So is it possible to have name if I use it as input pattern?
I'm looking for answers with R7RS, that have more of this type of edge cases covered.
All macros happens in compile time so runtime stuff might not exist. That means that you should think of it as syntax sugar and use it as susch. eg.
(for-each (macron something) '((1) (2) (3)))
Should then have an expansion based on that. Your current expansion is that it turns into this:
(for-each (lambda (x)
(eval (cons 'someting x) (interaction-environment))
'((1) (2) (3)))
For something being a macro this will apply the macro in runtime. It is bad. It also removes the need for the macro in the first place. You could do this instead:
(define (macron-proc name)
(lambda (x)
(eval (cons name x) (interaction-environment))))
(for-each (macron-proc 'something) '((1) (2) (3)))
I made a programming language that had passable macros:
(define xor (flambda (a b) `(if ,a (not ,b) ,b)))
(define (fold comb init lst)
(if (null? lst)
init
(fold comb (comb (car lst) init) (cdr lst))))
(fold xor #f '(#t #t)) ; ==> #f
It's not a very good approach if you are targeting an efficient compiled end product. The first macros were indeed like this and they removed it in LISP 1.5 before Common Lisp. Scheme avoided macros for many years and opted for syntax-rules in R4RS as an optional feature. R6RS is the only version that has full power macros.
With a procedure instead of macros this is actually the same as the following code with the bad eval removed:
(for-each (lambda (x)
(apply something x))
'((1) (2) (3)))
Which means you can implement macron much easier:
(define-syntax macron
(syntax-rules ()
((_ name)
(lambda (x)
(apply name x)))))
But from looking at this now you don't need a macro at all. This is partial application.
(define (partial proc arg)
(lambda (lst)
(apply proc arh lst)))
(map (partial + 3) '((1 2) (3 4) (4 5)))
; ==> (6 10 12)
There is actually a SRFI-26 called cut/cute which allows us to do something similar where it wraps it in a lambda:
(map (cut apply + 3 <>) '((1 2) (3 4) (4 5)))
The syntax-rules are the macros with the least power. You cannot do anything unhygienic and you cannot make new identifiers based on other ones. Eg. it' impossible to implement a racket style struct where you can do (struct complex [real imag]) and have the macro create complex?, complex-real, and complex-imag as procedures. You need to do as SRFI-57 does and require th euser to specify all the names such that you don't need to concatenate to new identifiers.
Right now R7RS-small only has syntax-rules. I think it was a mistake not to have a more powerful macro as an alternative since now the R7RS-large cannot be implemented with R7RS-small.

define-modify-macro with operator argument

In Section 12.4 of On Lisp, Paul Graham writes, "Unfortunately, we can't define a correct _f with define-modify-macro, because the operator to be applied to the generalized variable is given as an argument."
But what's wrong with something like this?
(define-modify-macro _f (op operand)
(lambda (x op operand)
(funcall op x operand)))
(let ((lst '(1 2 3)))
(_f (second lst) #'* 6)
lst)
=> (1 12 3)
Has there perhaps been a change made to define-modify-macro in ANSI Common Lisp that wasn't valid at the time On Lisp was written? Or are there reasons other than the one stated for not using define-modify-macro here?
It appears that Graham want's to be able to make a call such as
(_f * (second lst) 6)
rather than
(_f #'* (second lst) 6)
But surely that's not in keeping with a Lisp2 such as Common Lisp?
According to both Lispworks's Hyperspec and CLtL2 (look for define-modify-macro), the function is assumed to be a symbol (to a function or a macro). As far as I know, the following definition might not be conforming the specification:
(define-modify-macro _f (op operand)
(lambda (x op operand)
(funcall op x operand)))
But of course, it is possible that an implementation allows it.
To be sure you are conforming to the standard, you can define your own function, or even a macro:
(defmacro funcall-1 (val fun &rest args)
`(funcall ,fun ,val ,#args))
(define-modify-macro _ff (&rest args) funcall-1)
(let ((x (list 1 2 3 4)))
(_ff (third x) #'+ 10)
x)
If you wanted to have the function as a second argument, you could define another macro:
(defmacro ff (fun-form place &rest args)
`(_ff ,place ,fun-form ,#args))
Basically, your approach consists in wrapping funcall in define-modify-macro, and give the desired function as an argument of that function. At first sight, it looks like a hack, but as we can see below, this gives the same macroexanded code as the one in On Lisp, assuming we modify the latter a little.
The macroexpansion of the above is:
(LET ((X (LIST 1 2 3 4)))
(LET* ((#:G1164 X) (#:G1165 (FUNCALL #'+ (THIRD #:G1164) 10)))
(SB-KERNEL:%RPLACA (CDDR #:G1164) #:G1165))
X)
The version in On Lisp behaves as follows:
(defmacro _f (op place &rest args)
(multiple-value-bind (vars forms var set access)
(get-setf-expansion
place)
`(let* (,#(mapcar #'list vars forms)
(, (car var) (,op ,access ,#args)))
,set)))
(let ((x (list 1 2 3 4)))
(_f * (third x) 10)
x)
Macroexpansion:
(LET ((X (LIST 1 2 3 4)))
(LET* ((#:G1174 X) (#:G1175 (* (THIRD #:G1174) 10)))
(SB-KERNEL:%RPLACA (CDDR #:G1174) #:G1175))
X)
Here, the * is injected directly by the macroexpansion, which means that the resulting code has no possible runtime overhead (though compilers would probably handle your (funcall #'+ ...) equally well). If you pass #'+ to the macro, it fails to macroexpand. This is the major difference with your approach, but not a big limitation. In order to allow the On Lisp version to accept #'*, or even (create-closure) as an operator, it should be modified as follows:
(defmacro _f (op place &rest args)
(multiple-value-bind (vars forms var set access)
(get-setf-expansion
place)
`(let* (,#(mapcar #'list vars forms)
(, (car var) (funcall ,op ,access ,#args)))
,set)))
(see the call to funcall)
The previous example is then expanded as follows, for #'*:
(LET ((X (LIST 1 2 3 4)))
(LET* ((#:G1180 X) (#:G1181 (FUNCALL #'* (THIRD #:G1180) 10)))
(SB-KERNEL:%RPLACA (CDDR #:G1180) #:G1181))
X)
Now, it is exactly as your version. On Lisp uses _f to demonstrate how to use get-setf-expansion, and _f is a good example for that. But on the other hand, your implementation seems equally good.
On the question of whether one might prefer to pass * or #'*, we can also note that the define-modify-macro version of _f and #coredump's adapted version (with funcall) both accept lambda forms in the op position with or without #' e.g. both (lambda (x y) (* x y)) and #'(lambda (x y) (* x y)), whereas Graham's original version accepts only the former.
Interestingly in his book Let over Lambda, Doug Hoyte draws attention to a remark by Graham in his book ANSI Common Lisp that being able to omit the #' before a lambda form provides "a specious form of elegance at best" before going on to prefer to omit it.
I'm not taking a stand either way, merely pointing out that given Graham's choice for _f, the absence of the #' is no longer specious but necessary.

Evaluation of passed parameters inside macro body

I have a doubt on how parameters passed to the macros are getting evaluated, details below.
This macro is defined
(defmacro test-macro (xlist)
`(* ,#xlist))
and there is this global variable (defvar *test-list* '(1 100 2 200)).
When *test-list* is passed to this macro (test-macro *test-list*) , this error is returned -
value *TEST-LIST* is not of the expected type LIST.
[Condition of type TYPE-ERROR]
But if the function is modified to this, list is returned
(defmacro test-macro (xlist)
`(,#xlist)) ;; removed the * operator
(test-macro *test-list*) will return (1 100 2 200).
So my doubt is why ,#xlist is not getting evaluated in the first case, i.e when the * operator is applied. Any help is highly appreciated.
When debugging macros, The Right Way is to use macroexpand, not evaluate the macro forms. E.g., in your case:
(defmacro test-macro1 (xlist) `(* ,#xlist))
(macroexpand '(test-macro1 foo))
==> (* . FOO)
(defmacro test-macro2 (xlist) `(,#xlist))
(macroexpand '(test-macro2 foo))
==> FOO
neither is probably what you want.
The confusion is that the macro is a pre-processor: it has no built-in mechanism to know of runtime values. So when you use the term:
(test-macro test-list)
all that the macro sees is the identifier test-list: it does not know up-front that the runtime value is a list, only that the source program has used this variable identifier.
A macro is a source-to-source rewriter: it doesn't know about the dynamics of your program. A smarter compiler might be able to see that test-list is a constant and do an inlining, but the macro expander isn't that clever.
What you can do is probably something like this:
(defmacro test-macro (xlist)
(cond
(;; If we see test-macro is being used with a quoted list of things
;; then we can rewrite that statically.
(and (pair? xlist)
(eq? (car xlist) 'quote)
(list? (cadr xlist)))
`(list 'case-1 (* ,#(cadr xlist))))
(;; Also, if we see test-macro is being used with "(list ...)"
;; then we can rewrite that statically.
(and (pair? xlist)
(eq? (car xlist) 'list))
`(list 'case-2 (* ,#(cdr xlist))))
(else
;; Otherwise, do the most generic thing:
`(list 'case-3 (apply * ,xlist)))))
;; This hits the first case:
(test-macro '(3 4 5))
;; ... the second case:
(test-macro (list 5 6 7))
;; ... and the third case:
(defvar test-list '(1 100 2 200))
(test-macro test-list)
With regards to your second version: the macro:
(defmacro test-macro (xlist)
`(,#xlist))
is equivalent to:
(defmacro test-macro (xlist)
xlist)
so that's why you're not getting the error that you received in the first version.

Why does this Lisp macro as a whole work, even though each piece doesn't work?

I'm reading/working through Practical Common Lisp. I'm on the chapter about building a test framework in Lisp.
I have the function "test-+" implemented as below, and it works:
(defun test-+ ()
(check
(= (+ 1 2) 3)
(= (+ 5 6) 11)
(= (+ -1 -6) -7)))
Remember, I said, it works, which is why what follows is so baffling....
Here is some code that "test-+" refers to:
(defmacro check (&body forms)
`(combine-results
,#(loop for f in forms collect `(report-result ,f ',f))))
(defmacro combine-results (&body forms)
(with-gensyms (result)
`(let ((,result t))
,#(loop for f in forms collect `(unless ,f (setf ,result nil)))
,result)))
(defmacro with-gensyms ((&rest names) &body body)
`(let ,(loop for n in names collect `(,n (gensym)))
,#body))
(defun report-result (value form)
(format t "~:[FAIL~;pass~] ... ~a~%" value form)
value)
Now, what I've been doing is using Slime to macro-expand these, step by step (using ctrl-c RET, which is mapped to macroexpand-1).
So, the "check" call of "test-+" expands to this:
(COMBINE-RESULTS
(REPORT-RESULT (= (+ 1 2) 3) '(= (+ 1 2) 3))
(REPORT-RESULT (= (+ 5 6) 11) '(= (+ 5 6) 11))
(REPORT-RESULT (= (+ -1 -6) -7) '(= (+ -1 -6) -7)))
And then that macro-expands to this:
(LET ((#:G2867 T))
(UNLESS (REPORT-RESULT (= (+ 1 2) 3) '(= (+ 1 2) 3)) (SETF #:G2867 NIL))
(UNLESS (REPORT-RESULT (= (+ 5 6) 11) '(= (+ 5 6) 11)) (SETF #:G2867 NIL))
(UNLESS (REPORT-RESULT (= (+ -1 -6) -7) '(= (+ -1 -6) -7))
(SETF #:G2867 NIL))
#:G2867)
And it is THAT code, directly above this sentence, which doesn't work. If I paste that into the REPL, I get the following error (I'm using Clozure Common Lisp):
Unbound variable: #:G2867 [Condition of type UNBOUND-VARIABLE]
Now, if I take that same code, replace the gensym with a variable name such as "x", it works just fine.
So, how can we explain the following surprises:
The "test-+" macro, which calls all of this, works fine.
The macro-expansion of the "combine-results" macro does not run.
If I remove the gensym from the macro-expansion of "combine-results", it
does work.
The only thing I can speculate is that you cannot use code the contains literal usages of gensyms. If so, why not, and how does one work around that? And if that is not the explanation, what is?
Thanks.
GENSYM creates uninterned symbols. When the macro runs normally, this isn't a problem, because the same uninterned symbol is being substituted throughout the expression.
But when you copy and paste the expression into the REPL, this doesn't happen. #: tells the reader to return an uninterned symbol. As a result, each occurrence of #:G2867 is a different symbol, and you get the unbound variable warning.
If you do (setq *print-circle* t) before doing the MACROEXPAND it will use #n= and #n# notation to link the identical symbols together.
The code, after being printed and read back, is no longer the same code. In particular, the two instances of #:G2867 in the printed representation would be read back as two separated symbols (albeit sharing the same name), while they should be the same in the original internal representation.
Try setting *PRINT-CIRCLE* to T to preserve the identity in the printed representation of the macro-expanded code.