I'm trying to create a function on the fly that would return one constant value.
In JavaScript and other modern imperative languages I would use closures:
function id(a) {
return function() {return a;};
}
but Emacs lisp doesn't support those.
I can create mix of identity function and partial function application but it's not supported either.
So how do I do that?
Found another solution with lexical-let
(defun foo (n)
(lexical-let ((n n)) #'(lambda() n)))
(funcall (foo 10)) ;; => 10
Real (Not Fake) Closures in Emacs 24.
Although Emacs 24 has lexical scooping when the variable lexical-binding has value t, the defun special form doesn’t work properly in lexically bound contexts (at least not in Emacs 24.2.1.) This makes it difficult, but not impossible, to define real (not fake) closures. For example:
(let ((counter 0))
(defun counting ()
(setq counter (1+ counter))))
will not work as expected because the symbol counter in the defun will be bound to the global variable of that name, if there is one, and not the lexical variable define in the let. When the function counting is called, if the global variable doesn’t, exist then it will obviously fail. Hoever if there is such a global variable it be updated, which is probably not what was intended and could be a hard to trace bug since the function might appear to be working properly.
The byte compiler does give a warning if you use defun in this way and presumably the issue will be addressed in some future version of Emacs, but until then the following macro can be used:
(defmacro defun** (name args &rest body)
"Define NAME as a function in a lexically bound context.
Like normal `defun', except that it works correctly in lexically
bound contexts.
\(fn NAME ARGLIST [DOCSTRING] BODY...)"
(let ((bound-as-var (boundp `,name)))
(when (fboundp `,name)
(message "Redefining function/macro: %s" `,name))
(append
`(progn
(defvar ,name nil)
(fset (quote ,name) (lambda (,#args) ,#body)))
(if bound-as-var
'nil
`((makunbound `,name))))))
If you define counting as follows:
(let ((counter 0))
(defun** counting ()
(setq counter (1+ counter))))
it will work as expected and update the lexically bound variable count every time it is invoked, while returning the new value.
CAVEAT: The macro will not work properly if you try to defun** a function with the same name as one of the lexically bound variables. I.e if you do something like:
(let ((dont-do-this 10))
(defun** dont-do-this ()
.........
.........))
I can’t imagine anyone actually doing that but it was worth a mention.
Note: I have named the macro defun** so that it doesn’t clash with the macro defun* in the cl package, however it doesn’t depend in any way on that package.
Stupid idea: how about:
(defun foo (x)
`(lambda () ,x))
(funcall (foo 10)) ;; => 10
Emacs lisp only has dynamic scoping. There's a lexical-let macro that approximates lexical scoping through a rather terrible hack.
Emacs 24 has lexical binding.
http://www.emacswiki.org/emacs/LexicalBinding
;; -*- lexical-binding:t -*-
(defun create-counter ()
(let ((c 0))
(lambda ()
(setq c (+ c 1))
c)))
(setq counter (create-counter))
(funcall counter) ; => 1
(funcall counter) ; => 2
(funcall counter) ; => 3 ...
http://www.emacswiki.org/emacs/FakeClosures
Related
I'm trying to write an ELisp macro to generate a multiple functions based on some common data. For example, when I want to compute the fn names I write something like (I'm ignoring hygiene for the moment, I'm passing a symbol literal into the macro so evaluation shouldn't matter):
(cl-defmacro def-fns (sym)
"SYM."
(let ((s1 (make-symbol (concat (symbol-name sym) "-1")))
(s2 (make-symbol (concat (symbol-name sym) "-2"))))
`(progn (defun ,s1 () (+ 1 2 3))
(defun ,s2 () "six"))))
which I expect to generate 2 fns when invoked, called foo-1 and foo-2.
I should then be able to invoke the macro and fns like so:
(def-fns foo)
(foo-1)
;; => 6
(foo-2)
;; -> "six
Even the macroexpansion of (def-fns foo) in Emacs suggests that this should be the case:
(progn
(defun foo-1 nil (+ 1 2 3))
(defun foo-2 nil "six"))
However, when I evaluate the def-fns definition and invoke it it does not generate those functions. Why is this the case? This technique works in Common Lisp and in Clojure (which have very similar macro systems), so why not in ELisp?
Your code would not work in CL either.
The problem is with make-symbol - it creates a new symbol, so that
(eq (make-symbol "A") (make-symbol "A"))
==> nil
This means that your macro creates the functions but binds them to symbols which you no longer have a handle on.
When you evaluate (foo-1), Emacs Lisp reader tries to find the function binding of the interned symbol foo-1, not the fresh uninterned symbol your macro created.
You need to use intern instead: it makes the symbol "generally available", so to speak:
(eq (intern "a") (intern "a))
==> t
So, the corrected code looks like this:
(defmacro def-fns (sym)
"SYM."
(let ((s1 (intern (concat (symbol-name sym) "-1")))
(s2 (intern (concat (symbol-name sym) "-2"))))
`(progn (defun ,s1 () (+ 1 2 3))
(defun ,s2 () "six"))))
(def-fns foo)
(foo-1)
==> 6
(foo-2)
==> "six"
Notes:
If you were using CL, the uninterned symbols would have been printed as #:foo-1 and the source of your problem would have been obvious to you.
It is exceedingly rare that you really need to use make-symbol. Usually, you want to use either intern or gensym.
The scoping in Lisp is new to me and I think I've got it figured out, but the one area that confuses me a bit is how to mutate a global variable in a function without mentioning it specifically:
(defun empty-it (var)
"Remove everything from var."
(setf var nil))
Now, if I have *some-var* and call (empty-it *some-var*) it doesn't work, because the variables retains its contents from the scope prior to entering the function. Obviously, this works:
(defun empty-it-explicit ()
"Remove everything *some-var*."
(setf *some-var* nil))
Is it possible to have a general function that will clear the permanent contents of a stored variable, and have it work on any variable you pass to it? In other words, must you always explicitly mention a variable's name if you want it changed permanently?
(defun set-somevar-with-function (fn)
"Pass *some-var* into a function and set it to the results."
(setf *some-var* (funcall fn *some-var*)))
CL> (set-somevar-with-function #'empty-it)
Is this the correct Lisp idiom? If you had multiple vars you wanted to permanently mutate, would you have to write a separate function for each variable, each explicitly mentioning a different variable?
Basics
The scoping in Lisp is new to me and I think I've got it figured out,
but the one area that confuses me a bit is how to mutate a global
variable in a function without mentioning it specifically.
The scoping, aside from the availability of dynamically scoped variables, isn't really much different than what's available in other languages. E.g., in C, if you do something like:
void frob( int x ) {
x = 0;
}
int bar() {
int x = 3;
frob( x );
printf( "%d", x );
}
you'd expect to see 3 printed, not 0, because the x in frob and the x in bar are different variables. Modifying one doesn't change the value of the other. Now, in C you can take the address of a variable, and modify that variable through the pointer. You don't get pointers in Common Lisp, so you need something else if you want a layer of indirection. For lexical variables, you need to use closures for that purpose. For global variables (which are dynamically scoped), though, you can use the symbol that names the variable.
Direct modification of a variable (lexical or dynamic)
You can refer to global variables in the same way that you refer to any other variables in Common Lisp, by simply writing their name. You can modify them with setq or setf. E.g., you can do
(setq *x* 'new-value-of-x)
(setf *x* 'newer-value-of-x)
Indirect modification of a variable (dynamic only)
You can also take the symbol *x*, and use set or (setf symbol-value) to change the value:
(setf (symbol-value '*x*) 'newest-value-of-x)
(set '*x* 'newester-value-of-x)
Those cases give you some flexibility, because they mean that you can take the symbol as an argument, so you could do:
(defun set-somevar-with-function (var-name)
(setf (symbol-value var-name)
(funcall fn (symbol-value var-name))))
Understanding variable bindings (lexical and dynamic)
(Note: This is really just a rehashing of the C example above.) I think you understand why this bit of code that you posted doesn't work, but I want to mention a bit about it, just in case anyone with less experience comes across this question.
(defun empty-it (var)
"Remove everything from var."
(setf var nil))
Now, if I have *some-var* and call (empty-it *some-var*) it doesn't
work, because the variables retains its contents from the scope prior
to entering the function.
There's no unusual sense in which any variable is retaining or not retaining its value from one scope or another here. The evaluation model says that to evaluate (empty-it *some-var*), the system finds the function binding of empty-it and takes the value of *some-var*, let's call it x, and calls the function value of empty-it with the x. In doing that call, the variable var is bound to the value x. The call (setf var nil) modifies the variable var, and var has nothing to do with the variable *some-var*, except that for a while they happened to have the same value. Nothing here essentially depends on *some-var* being a global or dynamic variable, or on *some-var* and var having different names. You'd get the same results with another variable of the same name, e.g.:
(defun empty-it (var)
(setf var nil))
(let ((var 'value))
(empty-it var)
var)
;=> 'value
You'd even get the same if the parameter of empty-it were called *some-var*:
(defun empty-it (*some-var*)
(setf *some-var* nil))
(progn
(setf *some-var* 'value)
(empty-it *some-var*)
*some-var*)
;=> 'value
Beware of dynamic rebindings
Now, this will all work just fine if you're only modifying these variables, and you're never making new bindings for them. When you define a variable with defparameter or defvar, you're also globally proclaiming it special, i.e., dynamically scoped. The modifications done with set or setf are done to the most recent in scope binding of the variable. (When you modify a lexical variable, you're updating the innermost lexically enclosing binding.) This leads to results like the following:
(defparameter *x* 'first-value) ; AA
(defun call-and-modify (function name)
(setf (symbol-value name)
(funcall function
(symbol-value name))))
(progn
(let ((*x* 'second-value)) ; BB
(let ((*x* 'third-value)) ; CC
(print *x*) ; third-value (binding CC)
(call-and-modify (constantly 'fourth-value) '*x*)
(print *x*)) ; fourth-value (binding CC)
(print *x*)) ; second-value (binding BB)
(print *x*)) ; first-value (binding AA)
Symbols can be unbound with makunbound. Then the symbol is not just empty but gone. The danger, as always with mutation, is shared structure. hyperspec:makunbound
The symbol-function value of a symbol can be unbound with fmakunbound. hyperspec:fmakunbound
? (setf (symbol-value 'b) 42)
42
? (setf (symbol-function 'b)(lambda (x)(+ x 1)))
#<Anonymous Function #x210057DB6F>
? b
42
? (b 4)
5
? (fmakunbound 'b)
B
? b
42
? (b 4)
> Error: Undefined function B called with arguments (4) .
> ...[snipped]
> :pop
? b
42
? (makunbound 'b)
B
? b
> Error: Unbound variable: B
> ...[snipped]
> :pop
?
If you're looking for idiomatic lisp, I think (though I'm far from expert at lisp) the thing you want is to simply not have your function do the emptying. It can supply an empty value, just let that be it. So instead of having:
(defun empty-it (var)
(setf var nil))
; and then somewhere down the line calling:
(empty-it var)
You might do:
(defun empty ()
nil)
; and then somewhere down the line, call:
(setf var (empty))
Common-lisp is not limited to being (and maybe could be said simply not to be) a functional language, but for this, you'll want to take a (more) functional approach – meaning that your function may take a value, but it doesn't modify variables, it simply returns another value.
Of course, if your goal is to have the semantic expression of "make this thing empty", you could use a macro:
(defmacro empty-it (var)
`(setf ,var nil))
; and then, down the road, you can indeed call:
(empty-it var)
This would also be reasonably idiomatic.
I have various functions and I want to call each function with the same value. For instance,
I have these functions:
(defun OP1 (arg) ( + 1 arg) )
(defun OP2 (arg) ( + 2 arg) )
(defun OP3 (arg) ( + 3 arg) )
And a list containing the name of each function:
(defconstant *OPERATORS* '(OP1 OP2 OP3))
So far, I'm trying:
(defun TEST (argument) (dolist (n *OPERATORS*) (n argument) ) )
I've tried using eval, mapcar, and apply, but these haven't worked.
This is just a simplified example; the program that I'm writing has eight functions that are needed to expand nodes in a search tree, but for the moment, this example should suffice.
Other answers have provided some idiomatic solutions with mapcar. One pointed out that you might want a list of functions (which *operators* isn't) instead of a list of symbols (which *operators* is), but it's OK in Common Lisp to funcall a symbol. It's probably more common to use some kind of mapping construction (e.g., mapcar) for this, but since you've provided code using dolist, I think it's worth looking at how you can do this iteratively, too. Let's cover the (probably more idiomatic) solution with mapping first, though.
Mapping
You have a fixed argument, argument, and you want to be able to take a function function and call it with that `argument. We can abstract this as a function:
(lambda (function)
(funcall function argument))
Now, we want to call this function with each of the operations that you've defined. This is simple to do with mapcar:
(defun test (argument)
(mapcar (lambda (function)
(funcall function argument))
*operators*))
Instead of operators, you could also write '(op1 op2 op3) or (list 'op1 'op2 'op3), which are lists of symbols, or (list #'op1 #'op2 #'op3) which is a list of functions. All of these work because funcall takes a function designator as its first argument, and a function designator is
an object that denotes a function and that is one of: a symbol (denoting the function named by that symbol in the global environment), or a function (denoting itself).
Iteratively
You can do this using dolist. The [documentation for actually shows that dolist has a few more tricks up its sleeve. The full syntax is from the documentation
dolist (var list-form [result-form]) declaration* {tag | statement}*
We don't need to worry about declarations here, and we won't be using any tags, but notice that optional result-form. You can specify a form to produce the value that dolist returns; you don't have to accept its default nil. The common idiom for collecting values into a list in an iterative loop is to push each value into a new list, and then return the reverse of that list. Since the new list doesn't share structure with anything else, we usually reverse it destructively using nreverse. Your loop would become
(defun test (argument)
(let ((results '()))
(dolist (op *operators* (nreverse results))
(push (funcall op argument) results))))
Stylistically, I don't like that let that just introduces a single value, and would probably use an &aux variable in the function (but this is a matter of taste, not correctness):
(defun test (argument &aux (results '()))
(dolist (op *operators* (nreverse results))
(push (funcall op argument) results)))
You could also conveniently use loop for this:
(defun test2 (argument)
(loop for op in *operators*
collect (funcall op argument)))
You can also do somewhat succinctly, but perhaps less readably, using do:
(defun test3a (argument)
(do ((results '() (list* (funcall (first operators) argument) results))
(operators *operators* (rest operators)))
((endp operators) (nreverse results))))
This says that on the first iteration, results and operators are initialized with '() and *operators*, respectively. The loop terminates when operators is the empty list, and whenever it terminates, the return value is (nreverse results). On successive iterations, results is a assigned new value, (list* (funcall (first operators) argument) results), which is just like pushing the next value onto results, and operators is updated to (rest operators).
FUNCALL works with symbols.
From the department of silly tricks.
(defconstant *operators* '(op1 op2 o3))
(defun test (&rest arg)
(setf (cdr arg) arg)
(mapcar #'funcall *operators* arg))
There's a library, which is almost mandatory in any anywhat complex project: Alexandria. It has many useful functions, and there's also something that would make your code prettier / less verbose and more conscious.
Say, you wanted to call a number of functions with the same value. Here's how you'd do it:
(ql:quickload "alexandria")
(use-package :alexandria)
(defun example-rcurry (value)
"Calls `listp', `string' and `numberp' with VALUE and returns
a list of results"
(let ((predicates '(listp stringp numberp)))
(mapcar (rcurry #'funcall value) predicates)))
(example-rcurry 42) ;; (NIL NIL T)
(example-rcurry "42") ;; (NIL T NIL)
(defun example-compose (value)
"Calls `complexp' with the result of calling `sqrt'
with the result of calling `parse-integer' on VALUE"
(let ((predicates '(complexp sqrt parse-integer)))
(funcall (apply #'compose predicates) value)))
(example-compose "0") ;; NIL
(example-compose "-1") ;; T
Functions rcurry and compose are from Alexandria package.
Code that requires break statements or continue statements in other languages can be done with block & return-from or catch & throw in Common Lisp and Emacs Lisp. Then there is code that requires redo statements, or at least best written with redo. And redo statements don't have to be about loops. How can I do redo in Lisp?
If there was a redo equivalent in Lisp, I think it would work like this: special form with-redo which takes a symbol and forms, and redo which takes a symbol. The form (with-redo 'foo BODY-FORMS...) may contain (redo 'foo) in its BODY-FORMS, and (redo 'foo) transfers control back to the beginning of BODY-FORMS.
In Common Lisp:
(tagbody
start
(do-something)
(go start))
(dotimes (i some-list)
redo
(when (some-condition-p)
(go redo))
(some-more))
Rainer's answer illustrates the use of tagbody which is probably the easiest way to implement this kind of construct (a particular kind of goto, or unconditional jump). I thought it'd be nice to point out that if you don't want to use an explicit tagbody, or an implicit tagbody provided by one of the standard constructs, you can also create a with-redo just as you suggested. The only difference in this implementation is that we won't quote the tag, since they're not evaluted in tagbody, and being consistent with the other constructs is nice too.
(defmacro with-redo (name &body body)
`(macrolet ((redo (name)
`(go ,name)))
(tagbody
,name
,#body)))
CL-USER> (let ((x 0))
(with-redo beginning
(print (incf x))
(when (< x 3)
(redo beginning))))
1
2
3
; => NIL
Now this is actually a leaky abstraction, since the body could define other labels for the implicit tagbody, and could use go instead of redo, and so on. This might be desirable; lots of the built in iteration constructs (e.g., do, do*) use an implicit tagbody, so it might be OK. But, since you're also adding your own control flow operator, redo, you might want to make sure that it can only be used with tags defined by with-redo. In fact, while Perl's redo can be used with or without a label, Ruby's redo doesn't appear to allow a label. The label-less cases allow behavior of jumping back to the innermost enclosing loop (or, in our case, the innermost with-redo). We can address the leaky abstraction, as well as the ability to nest redos at the same time.
(defmacro with-redo (&body body)
`(macrolet ((redo () `(go #1=#:hidden-label)))
(tagbody
#1#
((lambda () ,#body)))))
Here we've defined a tag for use with with-redo that other things shouldn't know about (and can't find out unless they macroexpand some with-redo forms, and we've wrapped the body in a lambda function, which means that, e.g., a symbol in the body is a form to be evaluated, not a tag for tagbody. Here's an example showing that redo jumps back to the nearest lexically enclosing with-redo:
CL-USER> (let ((i 0) (j 0))
(with-redo
(with-redo
(print (list i j))
(when (< j 2)
(incf j)
(redo)))
(when (< i 2)
(incf i)
(redo))))
(0 0)
(0 1)
(0 2)
(1 2)
(2 2)
; => NIL
Of course, since you can define with-redo on your own, you can make the decisions about which design you want to adopt. Perhaps you like the idea of redo taking no arguments (and disguising a go with a secret label, but with-redo still being an implicit tagbody so that you can define other tags and jump to them with go; you can adapt the code here to do just that, too.
Some notes on implementation
This this answer has generated a few comments, I wanted to make a couple more notes about the implementation. Implementing with-redo with labels is pretty straightfoward, and I think that all the answers posted address it; the label-less case is a bit tricker.
First, the use of a local macrolet is a convenience that will get us warnings with redo is used outside of some lexically enclosing with-redo. E.g., in SBCL:
CL-USER> (defun redo-without-with-redo ()
(redo))
; in: DEFUN REDO-WITHOUT-WITH-REDO
; (REDO)
;
; caught STYLE-WARNING:
; undefined function: REDO
Second, the use of #1=#:hidden-label and #1# means that the go tag for redoing is an uninterned symbol (which lessens the likelihood that the abstraction leaks), but also is the same symbol across expansions of with-redo. In the following snippet tag1 and tag2 are the go-tags from two different expansions of with-redo.
(let* ((exp1 (macroexpand-1 '(with-redo 1 2 3)))
(exp2 (macroexpand-1 '(with-redo a b c))))
(destructuring-bind (ml bndgs (tb tag1 &rest rest)) exp1 ; tag1 is the go-tag
(destructuring-bind (ml bndgs (tb tag2 &rest rest)) exp2
(eq tag1 tag2))))
; => T
An alternative implementation of with-redo that uses a fresh gensym for each macroexpansion does not have this guarantee. For instance, consider with-redo-gensym:
(defmacro with-redo-gensym (&body body)
(let ((tag (gensym "REDO-TAG-")))
`(macrolet ((redo () `(go ,tag)))
(tagbody
,tag
((lambda () ,#body))))))
(let* ((exp1 (macroexpand-1 '(with-redo-gensym 1 2 3)))
(exp2 (macroexpand-1 '(with-redo-gensym a b c))))
(destructuring-bind (ml bndgs (tb tag1 &rest rest)) exp1
(destructuring-bind (ml bndgs (tb tag2 &rest rest)) exp2
(eq tag1 tag2))))
; => NIL
Now, it's worth asking whether this makes a practical difference, and if so, in which cases, and is it a difference for the better or the worse? Quite frankly, I'm not entirely sure.
If you were performing some complicated code manipulation after the inner macroexpansion of an (with-redo ...) form, form1, so that (redo) has already been turned into (go #1#), it means that moving the (go #1#) into the body of another (with-redo ...) form, form2, it will still have the effect of restarting an iteration in form2. In my mind, this makes it more like a return that could be transported from a block b1 into a different block b2, with the only difference it now returns from b2 instead of b1. I think that this is desirable, since we're trying to treat label-less with-redo and redo as primitive control structures.
Update: Emacs 24.4 (soon to be released) has tagbody. cl-lib that comes with Emacs 24.4 includes cl-tagbody.
For a dialect of Lisp which doesn't have tagbody, one can still implement redo as long as the dialect has a catch/throw equivalent.
For Emacs Lisp:
;; with-redo version 0.1
(defmacro with-redo (tag &rest body)
"Eval BODY allowing jumps using `throw'.
TAG is evalled to get the tag to use; it must not be nil.
Then the BODY is executed.
Within BODY, a call to `throw' with the same TAG and a non-nil VALUE causes a jump to the beginning of BODY.
A call to `throw' with the same TAG and nil as VALUE exits BODY and this `with-redo'.
If no throw happens, `with-redo' returns the value of the last BODY form."
(declare (indent 1))
(let ((ret (make-symbol "retval")))
`(let (,ret)
(while
(catch ,tag
(setq ,ret (progn ,#body))
nil))
,ret)))
(defun redo (symbol)
(throw symbol t))
Example of use (all examples are in Emacs Lisp):
(with-redo 'question
(let ((name (read-string "What is your name? ")))
(when (equal name "")
(message "Zero length input. Please try again.")
(beep)
(sit-for 1)
(redo 'question))
name))
Same example written as a mid-test loop instead:
(require 'cl-lib)
(let (name)
(cl-loop do
(setq name (read-string "What is your name? "))
while
(equal name "")
do
(message "Zero length input. Please try again.")
(beep)
(sit-for 1))
name)
Same example written as an infinite loop with a throw instead:
(let (name)
(catch 'question
(while t
(setq name (read-string "What is your name? "))
(unless (equal name "")
(throw 'question name))
(message "Zero length input. Please try again.")
(beep)
(sit-for 1))))
Implementing with-lex-redo-anon and lex-redo, where (lex-redo) causes a jump to the beginning of body of the textually/lexically innermost with-lex-redo-anon form:
;; with-lex-redo-anon version 0.1
(require 'cl-lib)
(defmacro with-lex-redo-anon (&rest body)
"Use with `(lex-redo)'."
(let ((tag (make-symbol "lex-redo-tag"))
(ret (make-symbol "retval")))
`(cl-macrolet ((lex-redo () '(cl-return-from ,tag t)))
(let (,ret)
(while
(cl-block ,tag
(setq ,ret (progn ,#body))
nil))
,ret))))
Example test:
(let ((i 0) (j 0))
(with-lex-redo-anon
(with-lex-redo-anon
(print (list i j))
(when (< j 2)
(incf j)
(lex-redo)))
(when (< i 2)
(incf i)
(lex-redo))))
Same output as in another answer.
I'm tring to apply closure in emacs lisp.And I find a post here:
How do I do closures in Emacs Lisp?
with some code like:
(defun foo (x) `(lambda () ,x)) (message (string (funcall (foo
66))))
But following the emacs documentation lambda should be formated like
'(lambda () x) ==> using this format ,I got an ERROR :Symbol's value as variable is void: x
When " , " is add betwenn "()" and "x" ,everything goes right .
Why?
This happens because Emacs Lisp is dynamically scoped thus foo returns a lambda where x is free. That's what the error tells you.
To do a closure in Emacs Lisp you have to use lexical-let which simulates a lexical binding and therefore allows you to make a real closure.
(defun foo (x)
(lexical-let ((x x))
(lambda () x)))
(message (string (funcall (foo 66))))
Here are some links from the Emacs Wiki:
Dynamic Binding Vs Lexical Binding
Fake Closures
Note that you could have defined x with a let like this:
(defun foo (x)
(lambda () x))
(message (string (let ((x 66)) (funcall
(foo 'i-dont-care)))))
This answer gives a bit of detail behind the first part of #Daimrod's correct answer.
Your question is why this works:
(defun foo (x) `(lambda () ,x)) (message (string (funcall (foo 66))))
and this doesn't work:
(defun foo (x) '(lambda () x)) (message (string (funcall (foo 66))))
First, the quote (') is unnecessary in the second, because in Emacs Lisp lambda forms are self-evaluating. That is, '(lambda (...) ...) generally acts the same as (lambda (...) ...).
But what does the backquote (`), instead of quote ('), do?
Inside a backquoted expression, a comma (,) means replace the next expression by its value, that is, evaluate it. So this:
`(lambda () ,x)
means create and return a list whose first element is the symbol lambda (that's not evaluated), whose second element is () (that's not evaluated), and whose third element is the value of variable x. It's equivalent to evaluating this code, which uses function list:
(list 'lambda '() x)
That's what you want: replace x by its current value (in this case, its value inside the function foo, that is, the value of foo's argument).
But this:
'(lambda () x)
(and likewise, because a lambda form is self-evaluating, (lambda () x)) returns this list: (lambda () x). And when that's evaluated using dynamic scoping (the default scoping regime in Emacs Lisp), x is unbound - it has no value. So a void-variable error is raised.