Make `define` evaluate its first argument in Racket - racket

In some dialects of LISP, there is a distinction between SET and SETQ, the first one evaluates its first argument so that you need to use the (SET (QUOTE …) …) syntax.
Since in Racket, quoting is not needed in definitions, define behaves as SETQ.
Is there a Racket function that behaves like SET? If no, how to write one?
I tried (define (SET a b) (define (eval a) b) b) but it does not seem to work when providing it to an other language with (provide SET).

Here's my quick attempt at this problem:
;; lib.rkt
#lang racket/base
(provide (rename-out [#set set]
[##%top #%top]
[#set! set!]
[#define define]))
(require syntax/parse/define)
(define env (make-hash))
(define (set x v stx)
(unless (hash-has-key? env x)
(raise-syntax-error #f "undefined id" stx))
(hash-set! env x v))
(define-simple-macro (##%top . x)
(hash-ref
env
'x
(λ () (raise-syntax-error #f "unbound id" (quote-syntax x)))))
(define (#set x v)
(set x v x))
(define-simple-macro (#set! x:id v)
(set 'x v (quote-syntax x)))
(define-simple-macro (#define x:id v)
(begin
(when (hash-has-key? env 'x)
(raise-syntax-error #f "id already defined" (quote-syntax x)))
(hash-set! env 'x v)))
#lang racket/base
(require "lib.rkt")
(define x 1)
(set (if #t 'x 'y) 2)
(add1 x) ; 3
(set! x 3)
(add1 x) ; 4
(add1 y) ; y: unbound id in: y
Note that this differs from original Racket in several ways. For example:
unbound ids are now reported at runtime instead of compile-time.
set! now won't work with set!-transformer.
define can't be used to define functions
define can't be used to shadow an identifier.
For (2) and (3), it's possible to get the original behavior back, but I don't want the answer to be too long, so I didn't include the full functionality. For now, I don't know how to solve (4).
Also note that you can only set identifiers defined via define. If you want to set identifiers defined via lambda, let, etc., you need to redefine these constructs too.

I would do it much less verbose and much simpler.
Since all arguments are evaluated, the set or let's say define% can be defined as a function!
(define (define% x y)
(eval `(define ,x ,y)))
One can even define functions using define% when using old-style form using lambda.
(define 'ab (lambda (x y) (+ x y)))
(ab 3 5) ;; 7
It even behaves correctly in terms of scope
(define (foo x)
(define% 'bar (lambda (x) (+ 1 x)))
(bar (bar (bar x))))
foo
;; #<procedure:foo>
bar
; bar: undefined;
; cannot reference undefined identifier
; [,bt for context]
(foo 3)
6
;; after first call however, bar is available in global environment
;; as pointed out by #AlexKnauf
bar
;; #<procedure:bar>
Thus there are some scoping issues ...
(let ((x 0))
(define% 'counter (lambda () (set! x (+ x 1)) x)))
counter
;; #<procedure>
(counter)
;; 1
(counter)
;; 2
(counter)
;; 3

Related

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.

Is defun or setf preferred for creating function definitions in common lisp and why?

What is the fundamental difference in the functions defined using defun and setf as below and is one method preferred over another outside of style considerations?
Using defun:
* (defun myfirst (l)
(car l) )
MYFIRST
* (myfirst '(A B C))
A
Using setf:
* (setf (fdefinition 'myfirst) #'(lambda (l) (car l)))
#<FUNCTION (LAMBDA (L)) {10021B477B}>
* (myfirst '(A B C))
A
If, as according to Wikipedia:
named functions are created by storing a lambda expression in a symbol using the defun macro
Using setf to create a variable in a different way requires the use of funcall:
* (defvar myfirst)
MYFIRST
* (setf myfirst (lambda (l) (car l)))
#<Interpreted Function (LAMBDA (X) (+ X X)) {48035001}>
* (funcall myfirst '(A B C))
A
My understanding is that this type of variable is different than the previous in that this variable is not found in the same namespace as the defun bound symbol as described in Why multiple namespaces?.
First of all, one should never underestimate the importance of style.
We write code not just for computers to run, but, much more importantly, for people to read.
Making code readable and understandable for people is a very important aspect of software development.
Second, yes, there is a big difference between (setf fdefinition) and defun.
The "small" differences are that defun can also set the doc string of the function name (actually, depending on how your imeplementation works, it might do that with lambda also), and creates a named block (seen in the macroexpansions below) which you would otherwise have to create yourself if you want to.
The big difference is that the compiler "knows" about defun and will process it appropriately.
E.g., if your file is
(defun foo (x)
(+ (* x x) x 1))
(defun bar (x)
(+ (foo 1 2 x) x))
then the compiler will probably warn you that you call foo in bar with the wrong number of arguments:
WARNING: in BAR in lines 3..4 : FOO was called with 3 arguments, but it requires 1
argument.
[FOO was defined in lines 1..2 ]
If you replace the defun foo with (setf (fdefinition 'foo) (lambda ...)), the compiler is unlikely to handle it as carefully. Moreover, you will probably get a warning along the lines of
The following functions were used but not defined:
FOO
You might want to examine what defun does in your implementation by macroexpanding it:
(macroexpand-1 '(defun foo (x) "doc" (print x)))
CLISP expands it to
(LET NIL (SYSTEM::REMOVE-OLD-DEFINITIONS 'FOO)
(SYSTEM::EVAL-WHEN-COMPILE
(SYSTEM::C-DEFUN 'FOO (SYSTEM::LAMBDA-LIST-TO-SIGNATURE '(X))))
(SYSTEM::%PUTD 'FOO
(FUNCTION FOO
(LAMBDA (X) "doc" (DECLARE (SYSTEM::IN-DEFUN FOO)) (BLOCK FOO (PRINT X)))))
(EVAL-WHEN (EVAL)
(SYSTEM::%PUT 'FOO 'SYSTEM::DEFINITION
(CONS '(DEFUN FOO (X) "doc" (PRINT X)) (THE-ENVIRONMENT))))
'FOO)
SBCL does:
(PROGN
(EVAL-WHEN (:COMPILE-TOPLEVEL) (SB-C:%COMPILER-DEFUN 'FOO NIL T))
(SB-IMPL::%DEFUN 'FOO
(SB-INT:NAMED-LAMBDA FOO
(X)
"doc"
(BLOCK FOO (PRINT X)))
(SB-C:SOURCE-LOCATION)))
The point here is that defun has a lot "under the hood", and for a reason. setf fdefinition is, on the other hand, more of "what you see is what you get", i.e., no magic involved.
This does not mean that setf fdefinition has no place in a modern lisp codebase. You can use it, e.g., to implement a "poor man's trace" (UNTESTED):
(defun trace (symbol)
(setf (get symbol 'old-def) (fdefinition symbol)
(fdefinition symbol)
(lambda (&rest args)
(print (cons symbol args))
(apply (get symbol 'old-def) args))))
(defun untrace (symbol)
(setf (fdefinition symbol) (get symbol 'old-def))
(remprop symbol 'odd-def))

Elisp lambdas, quoting, and lexical-let

I'm trying to understand the following two snippets of code:
(defun make-adder1 (n) `(lambda (x) (+ ,n x)))
(defun make-adder2 (n) (lexical-let ((n n)) (lambda (x) (+ n x))))
These both seem to produce callables:
(funcall (make-adder1 3) 5) ;; returns 8
(funcall (make-adder2 3) 5) ;; returns 8
These both work. I have two main questions:
1) I don't understand the disparity in "quoting level" between the two approaches. In the first case, the lambda expression is quoted, which means the "symbol itself" is returned instead of the value. In the second case, it seems like the statement with the lambda will get evaluated, so the value of the lambda will be returned. Yet, these both work with funcall. When using funcall on a defun'ed function, it has to be quoted. Is lexical-let doing some kind of quoting automatically? Isn't this, kind of surprising?
2) Reading other posts on this topic, I'm given to understand that the first approach will break down under certain circumstances and deviate from what one would expect from working with lambdas and higher order functions in other languages, because elisp has dynamic scoping by default. Can someone give a concrete example of code that makes this difference apparent and explain it?
In the first example there is no variable n in the resulting function, which is just (lambda (x) (+ 3 x)). It does not need lexical binding because there is no free variable in the lambda, i.e., no variable that needs to be kept in a binding of a closure. If you don't need the variable n to be available, as a variable in uses of the function, i.e., if its value at function definition time (=3) is all you need, then the first example is all you need.
(fset 'ad1 (make-adder1 3))
(symbol-function 'ad1)
returns:
(lambda (x) (+ 3 x))
The second example creates what is, in effect, a function that creates and applies a complicated closure.
(fset 'ad2 (make-adder2 3))
(symbol-function 'ad2)
returns
(lambda (&rest --cl-rest--)
(apply (quote (closure ((--cl-n-- . --n--) (n . 3) t)
(G69710 x)
(+ (symbol-value G69710) x)))
(quote --n--)
--cl-rest--))
A third option is to use a lexical-binding file-local variable and use the most straightforward definition. This creates a simple closure.
;;; foo.el --- toto -*- lexical-binding: t -*-
(defun make-adder3 (n) (lambda (x) (+ n x)))
(fset 'ad3 (make-adder3 3))
(symbol-function 'ad3)
returns:
(closure ((n . 3) t) (x) (+ n x))
(symbol-function 'make-adder1)
returns:
(lambda (n)
(list (quote lambda)
(quote (x))
(cons (quote +) (cons n (quote (x))))))
(symbol-function 'make-adder2)
returns:
(closure (t)
(n)
(let ((--cl-n-- (make-symbol "--n--")))
(let* ((v --cl-n--)) (set v n))
(list (quote lambda)
(quote (&rest --cl-rest--))
(list (quote apply)
(list (quote quote)
(function
(lambda (G69709 x)
(+ (symbol-value G69709) x))))
(list (quote quote) --cl-n--)
(quote --cl-rest--)))))
(symbol-function 'make-adder3)
returns
(closure (t) (n) (function (lambda (x) (+ n x))))

macro to feed a calculated binding list into a 'let'?

I'm trying different binding models for macro lambda lists.
Edit: in fact the lambda list for my test macros is always (&rest ...). Which means that I'm 'destructuring' the argument list and not the lambda list. I try to get a solution that works for combining optional with key arguments or rest/body with key arguments - both combinations don't work in the Common Lisp standard implementation.
So I have different functions giving me a list of bindings having the same syntax as used by 'let'.
E.g:
(build-bindings ...) => ((first 1) middle (last "three"))
Now I thought to use a simple macro inside my test macros feeding such a list to 'let'.
This is trivial if I have a literal list:
(defmacro let-list (_list &rest _body)
`(let ,_list ,#_body))
(let-list ((a 236)) a) => 236
But that's the same as a plain 'let'.
What I'd like to have is the same thing with a generated list.
So e.g.
(let-list (build-bindings ...)
(format t "first: ~s~%" first)
last)
with (build-bindings ...), evaluated in the same lexical scope as the call (let-list ...), returning
((first 1) middle (last "three"))
the expansion of the macro should be
(let
((first 1) middle (last "three"))
(format t "first: ~s~%" first)
last)
and should print 1 and return "three".
Any idea how to accomplish that?
Edit (to make the question more general):
If I have a list of (symbol value) pairs, i.e. same syntax that let requires for it's list of bindings, e.g. ((one 1) (two 'two) (three "three")), is there any way to write a macro that creates lexical bindings of the symbols with the supplied values for it's &rest/&body parameter?
This is seems to be a possible solution which Joshua pointed me to:
(let ((list_ '((x 23) (y 6) z)))
(let
((symbols_(loop for item_ in list_
collect (if (listp item_) (car item_) item_)))
(values_ (loop for item_ in list_
collect (if (listp item_) (cadr item_) nil))))
(progv symbols_ values_
(format t "x ~s, y ~s, z ~s~%" x y z))))
evaluates to:
;Compiler warnings :
; In an anonymous lambda form: Undeclared free variable X
; In an anonymous lambda form: Undeclared free variable Y
; In an anonymous lambda form: Undeclared free variable Z
x 23, y 6, z NIL
I could also easily rearrange my build-bindings functions to return the two lists needed.
One problem is, that the compiler spits warnings if the variables have never been declared special.
And the other problem that, if the dynamically bound variables are also used in a surrounding lexical binding, they a shadowed by the lexical binding - again if they have never been declared special:
(let ((x 47) (y 11) (z 0))
(let ((list_ '((x 23) (y 6) z)))
(let
((symbols_(loop for item_ in list_
collect (if (listp item_) (car item_) item_)))
(values_ (loop for item_ in list_
collect (if (listp item_) (cadr item_) nil))))
(progv symbols_ values_
(format t "x ~s, y ~s, z ~s~%" x y z)))))
evaluates to:
x 47, y 11, z 0
A better way could be:
(let ((x 47) (y 11) (z 0))
(locally
(declare (special x y))
(let ((list_ '((x 23) (y 6) z)))
(let
((symbols_(loop for item_ in list_
collect (if (listp item_) (car item_) item_)))
(values_ (loop for item_ in list_
collect (if (listp item_) (cadr item_) nil))))
(progv symbols_ values_
(format t "x ~s, y ~s, z ~s~%" x y z))))))
evaluates to:
;Compiler warnings about unused lexical variables skipped
x 23, y 6, z NIL
I can't see at the moment whether there are other problems with the dynamic progv bindings.
But the whole enchilada of a progv wrapped in locally with all the symbols declared as special cries for a macro again - which is again not possible due to same reasons let-list doesn't work :(
The possiblilty would be a kind of macro-lambda-list destructuring-hook which I'm not aware of.
I have to look into the implementation of destructuring-bind since that macro does kind of what I'd like to do. Perhaps that will enlight me ;)
So a first (incorrect) attempt would look something like this:
(defun build-bindings ()
'((first 1) middle (last "three")))
(defmacro let-list (bindings &body body)
`(let ,bindings
,#body))
Then you could try doing something like:
(let-list (build-bindings)
(print first))
That won't work, of course, because the macro expansion leaves the form (build-bindings) in the resulting let, in a position where it won't be evaluated:
CL-USER> (pprint (macroexpand-1 '(let-list (build-bindings)
(print first))))
(LET (BUILD-BINDINGS)
(PRINT FIRST))
Evaluation during Macroexpansion time
The issue is that you want the result of build-bindings at macroexpansion time, and that's before the code as a whole is run. Now, in this example, build-bindings can be run at macroexpansion time, because it's not doing anything with any arguments (remember I asked in a comment what the arguments are?). That means that you could actually eval it in the macroexpansion:
(defmacro let-list (bindings &body body)
`(let ,(eval bindings)
,#body))
CL-USER> (pprint (macroexpand-1 '(let-list (build-bindings)
(print first))))
(LET ((FIRST 1) MIDDLE (LAST "three"))
(PRINT FIRST))
Now that will work, insofar as it will bind first, middle, and last to 1, nil, and "three", respectively. However, if build-bindings actually needed some arguments that weren't available at macroexpansion time, you'd be out of luck. First, it can take arguments that are available at macroexpansion time (e.g., constants):
(defun build-bindings (a b &rest cs)
`((first ',a) (middle ',b) (last ',cs)))
CL-USER> (pprint (macroexpand-1 '(let-list (build-bindings 1 2 3 4 5)
(print first))))
(LET ((FIRST '1) (MIDDLE '2) (LAST '(3 4 5)))
(PRINT FIRST))
You could also have some of the variables appear in there:
(defun build-bindings (x ex y why)
`((,x ,ex) (,y ,why)))
CL-USER> (pprint (macroexpand-1 '(let-list (build-bindings 'a 'ay 'b 'bee)
(print first))))
(LET ((A AY) (B BEE))
(PRINT FIRST))
What you can't do, though, is have the variable names be determined from values that don't exist until runtime. E.g., you can't do something like:
(let ((var1 'a)
(var2 'b))
(let-list (build-bindings var1 'ay var2 'bee)
(print first))
because (let-list (build-bindings …) …) is macroexpanded before any of this code is actually executed. That means that you'd be trying to evaluate (build-bindings var1 'ay var2 'bee) when var1 and var2 aren't bound to any values.
Common Lisp does all its macroexpansion first, and then evaluates code. That means that values that aren't available until runtime are not available at macroexpansion time.
Compilation (and Macroexpansion) at Runtime
Now, even though I said that Common Lisp does all its macroexpansion first, and then evaluates code, the code above actually uses eval at macroexpansion to get some extra evaluation earlier. We can do things in the other direction too; we can use compile at runtime. That means that we can generate a lambda function and compile it based on code (e.g., variable names) provided at runtime. We can actually do this without using a macro:
(defun %dynamic-lambda (bindings body)
(flet ((to-list (x) (if (listp x) x (list x))))
(let* ((bindings (mapcar #'to-list bindings))
(vars (mapcar #'first bindings))
(vals (mapcar #'second bindings)))
(apply (compile nil `(lambda ,vars ,#body)) vals))))
CL-USER> (%dynamic-lambda '((first 1) middle (last "three"))
'((list first middle last)))
;=> (1 NIL "three")
This compiles a lambda expression that is created at runtime from a body and a list of bindings. It's not hard to write a macro that takes some fo the quoting hassle out of the picture:
(defmacro let-list (bindings &body body)
`(%dynamic-lambda ,bindings ',body))
CL-USER> (let-list '((first 1) middle (last "three"))
(list first middle last))
;=> (1 NIL "three")
CL-USER> (macroexpand-1 '(let-list (build-bindings)
(list first middle last)))
;=> (%DYNAMIC-LAMBDA (BUILD-BINDINGS) '((LIST FIRST MIDDLE LAST)))
CL-USER> (flet ((build-bindings ()
'((first 1) middle (last "three"))))
(let-list (build-bindings)
(list first middle last)))
;=> (1 NIL "three")
This gives you genuine lexical variables from a binding list created at runtime. Of course, because the compilation is happening at runtime, you lose access to the lexical environment. That means that the body that you're compiling into a function cannot access the "surrounding" lexical scope. E.g.:
CL-USER> (let ((x 3))
(let-list '((y 4))
(list x y)))
; Evaluation aborted on #<UNBOUND-VARIABLE X {1005B6C2B3}>.
Using PROGV and special variables
If you don't need lexical variables, but can use special (i.e., dynamically scoped) variables instead, you can establish bindings at runtime using progv. That would look something like:
(progv '(a b c) '(1 2 3)
(list c b a))
;;=> (3 2 1)
You'll probably get some warnings with that if run it, because when the form is compiled, there's no way to know that a, b, and c are supposed to be special variables. You can use locally to add some special declarations, though:
(progv '(a b c) '(1 2 3)
(locally
(declare (special a b c))
(list c b a)))
;;=> (3 2 1)
Of course, if you're doing this, then you have to know the variables in advance which is exactly what you were trying to avoid in the first place. However, if you're willing to know the names of the variables in advance (and your comments seem like you might be okay with that), then you can actually use lexical variables.
Lexical variables with values computed at run time
If you're willing to state what the variables will be, but still want to compute their values dynamically at run time, you can do that relatively easily. First, lets write the direct version (with no macro):
;; Declare three lexical variables, a, b, and c.
(let (a b c)
;; Iterate through a list of bindings (as for LET)
;; and based on the name in the binding, assign the
;; corresponding value to the lexical variable that
;; is identified by the same symbol in the source:
(dolist (binding '((c 3) (a 1) b))
(destructuring-bind (var &optional value)
(if (listp binding) binding (list binding))
(ecase var
(a (setf a value))
(b (setf b value))
(c (setf c value)))))
;; Do something with the lexical variables:
(list a b c))
;;=> (1 NIL 3)
Now, it's not too hard to write a macrofied version of this. This version isn't perfect, (e.g., there could be hygiene issues with names, and declarations in the body won't work (because the body is being spliced in after some stuff). It's a start, though:
(defmacro computed-let (variables bindings &body body)
(let ((assign (gensym (string '#:assign-))))
`(let ,variables
(flet ((,assign (binding)
(destructuring-bind (variable &optional value)
(if (listp binding) binding (list binding))
(ecase variable
,#(mapcar (lambda (variable)
`(,variable (setf ,variable value)))
variables)))))
(map nil #',assign ,bindings))
,#body)))
(computed-let (a b c) '((a 1) b (c 3))
(list a b c))
;;=> (1 NIL 3)
One way of making this cleaner would be to avoid the assignment altogether, and the computed values to provide the values for the binding directly:
(defmacro computed-let (variables bindings &body body)
(let ((values (gensym (string '#:values-)))
(variable (gensym (string '#:variable-))))
`(apply #'(lambda ,variables ,#body)
(let ((,values (mapcar #'to-list ,bindings)))
(mapcar (lambda (,variable)
(second (find ,variable ,values :key 'first)))
',variables)))))
This version creates a lambda function where the arguments are the specified variables and the body is the provided body (so the declarations in the body are in an appropriate place), and then applies it to a list of values extracted from the result of the computed bindings.
Using LAMBDA or DESTRUCTURING-BIND
since I'm doing some "destructuring" of the arguments (in a bit a different way), I know which arguments must be present or have which
default values in case of missing optional and key arguments. So in
the first step I get a list of values and a flag whether an optional
or key argument was present or defaulted. In the second step I would
like to bind those values and/or present/default flag to local
variables to do some work with them
This is actually starting to sound like you can do what you need to by using a lambda function or destructuring-bind with keyword arguments. First, note that you can use any symbol as a keyword argument indicator. E.g.:
(apply (lambda (&key
((b bee) 'default-bee b?)
((c see) 'default-see c?))
(list bee b? see c?))
'(b 42))
;;=> (42 T DEFAULT-SEE NIL)
(destructuring-bind (&key ((b bee) 'default-bee b?)
((c see) 'default-see c?))
'(b 42)
(list bee b? see c?))
;;=> (42 T DEFAULT-SEE NIL)
So, if you just make your function return bindings as a list of keyword arguments, then in the destructuring or function application you can automatically bind corresponding variables, assign default values, and check whether non-default values were provided.
Acting a bit indirectly:
a solution that works for combining optional with key arguments or
rest/body with key arguments
Have you considered the not-entirely-uncommon paradigm of using a sub-list for the keywords?
e.g.
(defmacro something (&key (first 1) second) &body body) ... )
or, a practical use from Alexandria:
(defmacro with-output-to-file ((stream-name file-name
&rest args
&key (direction nil direction-p)
&allow-other-keys)
&body body)

Renaming lambda in Common Lisp

I started learning Common Lisp recently, and (just for fun) decided to rename the lambda macro.
My attempt was this:
> (defmacro λ (args &body body) `(lambda ,args ,#body))
It seems to expand correctly when by itself:
> (macroexpand-1 '(λ (x) (* x x)))
(LAMBDA (X) (* X X))
But when it's nested inside an expression, execution fails:
> ((λ (x) (* x x)) 2)
(Λ (X) (* X X)) is not a function name; try using a symbol instead
I am probably missing something obvious about macro expansion, but couldn't find out what it is.
Maybe you can help me out?
edit:
It does work with lambda:
> ((lambda (x) (* x x)) 2)
4
edit 2:
One way to make it work (as suggested by Rainer):
> (set-macro-character #\λ (lambda (stream char) (quote lambda)))
(tested in Clozure CL)
In Common Lisp LAMBDA is two different things: a macro and a symbol which can be used in a LAMBDA expression.
The LAMBDA expression:
(function (lambda (x) (foo x)))
shorter written as
#'(lambda (x) (foo x))
An applied lambda expression is also valid:
((lambda (x) (+ x x)) 4)
Above both forms are part of the core syntax of Common Lisp.
Late in the definition of Common Lisp a macro called LAMBDA has been added. Confusingly enough, but with good intentions. ;-) It is documented as Macro LAMBDA.
(lambda (x) (+ x x))
expands into
(function (lambda (x) (+ x x))
It makes Common Lisp code look slightly more like Scheme code and then it is not necessary to write
(mapcar #'(lambda (x) (+ x x)) some-list)
With the LAMBDA macro we can write
(mapcar (lambda (x) (+ x x)) some-list)
Your example fails because
((my-lambda (x) (* x x)) 2)
is not valid Common Lisp syntax.
Common Lisp expects either
a data object
a variable
a function call in the form (function args...)
a function call in the form ((lambda (arglist ...) body) args...)
a macro form like (macro-name forms...)
a special form using one of the built-in special operators like FUNCTION, LET, ...
defined in the list of special operators in Common Lisp
As you can see a syntax of
((macro-name forms...) forms...)
is not a part of Common Lisp.
It is possible to read the character λ as LAMBDA:
(defun λ-reader (stream char)
(declare (ignore char stream))
'LAMBDA)
(set-macro-character #\λ #'λ-reader)
Example:
CL-USER 1 > ((λ (x) (* x x)) 3)
9
CL-USER 2 > '(λ (x) (* x x))
(LAMBDA (X) (* X X))
You might also think of LAMBDA as an operator which, given a term and a list of free variables, returns a function. This p.o.v. takes LAMBDA out of the family of basic functions and elementary macros -- at least as far as the interpreter is concerned.
(defun lambda-char (stream char)
"A lambda with only ONE arg _"
(declare (ignore char))
(let ((codes (read stream nil)))
`(lambda (_) ,codes)))
(set-macro-character #\λ #'lambda-char t)
λ(+ 1 2 _) ; => (lambda (_) (+ 1 2 _))
Maybe this is more concise, with ONLY ONE arg of _