Emacs lisp high-order function support - emacs

I am trying to implement Haskell-like high-order function in Elisp, using closures.
;;; -*- lexical-binding: t -*-
(defun foo (pair)
(car pair))
(defun* .curry (fn)
(lambda (x y &rest args) (apply fn (cons x y) args)))
((lambda (x y) (1+ x)) 2 3)
((lambda (&rest args) (apply (.curry #'foo) args)) 2 3)
(funcall (.curry #'foo) 2 3)
((.curry #'foo) 2 3)
Problem is that last line returns error Invalid function. So, it seems closure do not considered sane function. I still can use (.curry #'foo) in mapc, but not in hooks.
Is it something I can do about it?

Your ((.curry #'foo) 2 3) is invalid in any Lisp I know of except Scheme (and Scheme derivatives such as Racket). The simplest code that illustrates the issue is as follows:
(defun f () (lambda ()))
(funcall (f)) ; tested in Emacs 23 and CLISP, works
((f)) ; tested in Emacs 23 and CLISP, results in an error

Related

Common Lisp macro let-curry - not working

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

LISP: how to trace macros

This is probably a stupid question, but I'm walking through the PG lisp book, and I wanted to step through some example macros that he provides with actual values, for instance:
(defmacro our-let (binds &body body)
`(
(lambda ,(
mapcar #'(lambda (x) (if (consp x) (car x) x)) binds
)
,#body
)
,#(mapcar #'(lambda (x) (if (consp x) (cadr x) nil)) binds)
)
)
I naively tried to run (trace our-let) and then (our-let ((x 1) (y 2)) (+ x y)) but I'm getting an error, can't use encapsulation to trace anonymous function #<FUNCTION (MACRO-FUNCTION OUR-LET) {22675BBB}>. Also not sure how to best put print statements into the lambdas. What's the best way to debug this macro/output how it's processing inputs?
EDIT(1): I had the incorrect formatting for macroexpand, which works.
Actually being able to trace macros is not very common in Common Lisp implementations. Compilers will typically expand the macro forms during compilation.
A few implementations support it though - which makes sense when they also support a Lisp interpreter, which runs the actual source. Among those are LispWorks and CLISP.
Here using the code from Sylwester in CLISP:
i i i i i i i ooooo o ooooooo ooooo ooooo
I I I I I I I 8 8 8 8 8 o 8 8
I \ `+' / I 8 8 8 8 8 8
\ `-+-' / 8 8 8 ooooo 8oooo
`-__|__-' 8 8 8 8 8
| 8 o 8 8 o 8 8
------+------ ooooo 8oooooo ooo8ooo ooooo 8
Welcome to GNU CLISP 2.49.93+ (2018-02-18) <http://clisp.org/>
Copyright (c) Bruno Haible, Michael Stoll 1992-1993
Copyright (c) Bruno Haible, Marcus Daniels 1994-1997
Copyright (c) Bruno Haible, Pierpaolo Bernardi, Sam Steingold 1998
Copyright (c) Bruno Haible, Sam Steingold 1999-2000
Copyright (c) Sam Steingold, Bruno Haible 2001-2018
Type :h and hit Enter for context help.
[1]> (defmacro our-let ((&rest bindings) &body body)
(let ((names (mapcar #'(lambda (x) (if (consp x) (car x) x)) bindings))
(exprs (mapcar #'(lambda (x) (if (consp x) (cadr x) nil)) bindings)))
`((lambda ,names ,#body) ,#exprs)))
OUR-LET
[2]> (trace our-let)
;; Tracing macro OUR-LET.
(OUR-LET)
[3]> (dotimes (i 3)
(our-let ((x (* i 10)))
(+ x 3)))
1. Trace: (OUR-LET ((X (* I 10))) (+ X 3))
1. Trace: OUR-LET ==> ((LAMBDA (X) (+ X 3)) (* I 10))
1. Trace: (OUR-LET ((X (* I 10))) (+ X 3))
1. Trace: OUR-LET ==> ((LAMBDA (X) (+ X 3)) (* I 10))
1. Trace: (OUR-LET ((X (* I 10))) (+ X 3))
1. Trace: OUR-LET ==> ((LAMBDA (X) (+ X 3)) (* I 10))
NIL
[4]>
How you debug it:
(macroexpand-1 '(our-let ((x 1) (y 2)) (+ x y)))
; ==> ((lambda (X Y) (+ X Y)) 1 2)
; ==> t
BTW your formatting is not good. Here is how it can look:
(defmacro our-let (binds &body body)
`((lambda ,(mapcar #'(lambda (x) (if (consp x) (car x) x)) binds)
,#body)
,#(mapcar #'(lambda (x) (if (consp x) (cadr x) nil)) binds)))
Or I would prefer:
(defmacro our-let ((&rest bindings) &body body)
(let ((names (mapcar #'(lambda (x) (if (consp x) (car x) x)) bindings))
(exprs (mapcar #'(lambda (x) (if (consp x) (cadr x) nil)) bindings)))
`((lambda ,names ,#body) ,#exprs)))
A nice thing about CL is that its designers thought quite hard about some things. In particular it turns out that you can trace macroexpansion portably in CL, thanks to *macroexpand-hook*. The code at the end of this answer uses it to trace macroexpansion It makes some attempt to cooperate with anything else which might be talking to *macroexpand-hook*, and to avoid recursive tracing, but it's not very well tested. There are controls for how much should be printed which have default values which are 'much less than everything'.
Here is an example of this in LispWorks:
> (macroexpand-traced-p)
nil
> (trace-macroexpand)
t
> (defun foo (x) x)
(defun foo (x) ...)
-> (dspec:def (defun foo) (dspec:install-defun 'foo # ...))
(dspec:def (defun foo) (dspec:install-defun 'foo # ...))
-> (compiler-let (#) (compiler::top-level-form-name # #))
(compiler::top-level-form-name (defun foo)
(dspec:install-defun 'foo # ...))
-> (compiler::tlf-name-binding (compiler-let #)
(dspec:install-defun 'foo # ...))
(compiler::tlf-name-binding (compiler-let #)
(dspec:install-defun 'foo # ...))
-> (compiler-let (# #) (dspec:install-defun 'foo # ...))
(dspec:location)
-> ':listener
foo
As you can see you get a lot of internal expansions which are probably not interesting. To deal with this there is support for filtering the output so you don't see macroexpansions which may not be interesting to you, of which there are a lot.
Here is a filter function which tries to only show expansions where the thing being expanded is visible in the current package:
(defun trace-macroexpand-trace-this-package-p (macro-function macro-form
environment)
(declare (ignore macro-function environment))
(and (consp macro-form)
(symbolp (first macro-form))
(let ((name (first macro-form)))
(eq (find-symbol (symbol-name name) *package*) name))))
And here is the some output for that:
> (setf *trace-macroexpand-trace-p* #'trace-macroexpand-trace-this-package-p)
(setf *trace-macroexpand-trace-p*
#'trace-macroexpand-trace-this-package-p)
-> (let* (#) (setq *trace-macroexpand-trace-p* #:|Store-Var-1102|))
#<Function trace-macroexpand-trace-this-package-p 4060000844>
> (defun foo (x) x)
(defun foo (x) ...)
-> (dspec:def (defun foo) (dspec:install-defun 'foo # ...))
foo
As you can see you only now get 'interesting' macroexpansions. Cleverer filters could be defined, of course.
Here is the code:
(eval-when (:load-toplevel :compile-toplevel :execute)
;; macroexpansion tracing really wants to be off when compiling this
;; code as exciting things may happen during the evaluation of
;; DEFVAR &c otherwise.
(when (fboundp 'trace-macroexpand)
(ignore-errors ;don't barf
(trace-macroexpand nil))))
(defvar *trace-macroexpand-print-length* 3
"The value of *PRINT-LENGTH* used when tracing macroexpansions")
(defvar *trace-macroexpand-print-level* 2
"The value of *PRINT-LEVEL* used when tracing macroexpansions")
(defvar *trace-macroexpand-trace-p* (constantly t)
"Should we trace a given macroexpansion?
If this is bound to a function that function will be called with the
same three arguments that *MACROEXPAND-HOOK* takes, and should return
true if the expansion is to be printed. Otherwise it should be true
if expansion is to be printed, false otherwise.")
(defvar *traced-macroexpand-hook*
;; the old value of *MACROEXPAND-HOOK*, used to restore it and to
;; know if we should trace. Not user-adjustable.
nil)
(defun trace-macroexpand (&optional (tracep t))
"Trace or untrace macroexpansion.
If called with no argument, or an argument which is true, ensure that
macroexpansion is on. If it was already on return NIL, otherwise
return T.
If called with an argument which is NIL then ensure macroexpansion is
not traced. If it was traced return T else return NIL."
(if tracep
(if *traced-macroexpand-hook*
nil
(let ((hook *macroexpand-hook*))
(flet ((macroexpand-hook (macro-function macro-form environment)
(if (if (functionp *trace-macroexpand-trace-p*)
(funcall *trace-macroexpand-trace-p*
macro-function macro-form environment)
*trace-macroexpand-trace-p*)
(let ((expanded-form (funcall hook macro-function
macro-form environment))
(*print-length* *trace-macroexpand-print-length*)
(*print-level* *trace-macroexpand-print-level*)
(*print-pretty* t))
(format *debug-io* "~&~S~% -> ~S~%" macro-form expanded-form)
expanded-form)
(funcall hook macro-function macro-form environment))))
(setf *traced-macroexpand-hook* hook
*macroexpand-hook* #'macroexpand-hook)
t)))
(if *traced-macroexpand-hook*
(progn
(setf *macroexpand-hook* *traced-macroexpand-hook*
*traced-macroexpand-hook* nil)
t)
nil)))
(defun macroexpand-traced-p ()
"Is macroexpansion currently traced?"
(if *traced-macroexpand-hook* t nil))
Here is one way to trace the macro that should work in any Common Lisp:
(eval-when (:compile-toplevel :load-toplevel :execute)
(defun our-let-expander (binds body)
`((lambda ,(mapcar #'(lambda (x) (if (consp x) (car x) x)) binds)
,#body)
,#(mapcar #'(lambda (x) (if (consp x) (cadr x) nil)) binds))))
(defmacro our-let (binds &body body)
(our-let-expander binds body))
Now we just (trace our-let-expander).
In my experience, complicated macros often end up handled via expander helper functions like this anyway, for various reasons.
(One big reason is this: as soon as you have two or more syntactic interfaces to the same expansion logic, you don't want to copy and paste that logic into multiple defmacro forms, but have it in a function.)
P.S. note the reformatting of the backquote form. Do not separate opening parentheses from what follows, and have closing parentheses on lines by themselves.

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))))

Tacit programming in Lisp

Is it possible to use/implement tacit programming (also known as point-free programming) in Lisp? And in case the answer is yes, has it been done?
This style of programming is possible in CL in principle, but, being a Lisp-2, one has to add several #'s and funcalls. Also, in contrast to Haskell for example, functions are not curried in CL, and there is no implicit partial application. In general, I think that such a style would not be very idiomatic CL.
For example, you could define partial application and composition like this:
(defun partial (function &rest args)
(lambda (&rest args2) (apply function (append args args2))))
(defun comp (&rest functions)
(flet ((step (f g) (lambda (x) (funcall f (funcall g x)))))
(reduce #'step functions :initial-value #'identity)))
(Those are just quick examples I whipped up – they are not really tested or well thought-through for different use-cases.)
With those, something like map ((*2) . (+1)) xs in Haskell becomes:
CL-USER> (mapcar (comp (partial #'* 2) #'1+) '(1 2 3))
(4 6 8)
The sum example:
CL-USER> (defparameter *sum* (partial #'reduce #'+))
*SUM*
CL-USER> (funcall *sum* '(1 2 3))
6
(In this example, you could also set the function cell of a symbol instead of storing the function in the value cell, in order to get around the funcall.)
In Emacs Lisp, by the way, partial application is built-in as apply-partially.
In Qi/Shen, functions are curried, and implicit partial application (when functions are called with one argument) is supported:
(41-) (define comp F G -> (/. X (F (G X))))
comp
(42-) ((comp (* 2) (+ 1)) 1)
4
(43-) (map (comp (* 2) (+ 1)) [1 2 3])
[4 6 8]
There is also syntactic threading sugar in Clojure that gives a similar feeling of "pipelining":
user=> (-> 0 inc (* 2))
2
You could use something like (this is does a little more than -> in
Clojure):
(defmacro -> (obj &rest forms)
"Similar to the -> macro from clojure, but with a tweak: if there is
a $ symbol somewhere in the form, the object is not added as the
first argument to the form, but instead replaces the $ symbol."
(if forms
(if (consp (car forms))
(let* ((first-form (first forms))
(other-forms (rest forms))
(pos (position '$ first-form)))
(if pos
`(-> ,(append (subseq first-form 0 pos)
(list obj)
(subseq first-form (1+ pos)))
,#other-forms)
`(-> ,(list* (first first-form) obj (rest first-form))
,#other-forms)))
`(-> ,(list (car forms) obj)
,#(cdr forms)))
obj))
(you must be careful to also export the symbol $ from the package in
which you place -> - let's call that package tacit - and put
tacit in the use clause of any package where you plan to use ->, so -> and $ are inherited)
Examples of usage:
(-> "TEST"
string-downcase
reverse)
(-> "TEST"
reverse
(elt $ 1))
This is more like F#'s |> (and the shell pipe) than Haskell's ., but they
are pretty much the same thing (I prefer |>, but this is a matter of personal taste).
To see what -> is doing, just macroexpand the last example three times (in SLIME, this is accomplished by putting the cursor on the first ( in the example and typing C-c RET three times).
YES, it's possible and #danlei already explained very well. I am going to add up some examples from the book ANSI Common Lisp by Paul Graham, chapter 6.6 on function builders:
you can define a function builder like this:
(defun compose (&rest fns)
(destructuring-bind (fn1 . rest) (reverse fns)
#'(lambda (&rest args)
(reduce #'(lambda (v f) (funcall f v))
rest
:initial-value (apply fn1 args)))))
(defun curry (fn &rest args)
#'(lambda (&rest args2)
(apply fn (append args args2))))
and use it like this
(mapcar (compose #'list #'round #'sqrt)
'(4 9 16 25))
returns
((2) (3) (4) (5))
The compose function call:
(compose #'a #'b #'c)
is equlvalent to
#'(lambda (&rest args) (a (b (apply #'c args))))
This means compose can take any number of arguments, yeah.
Make a function which add 3 to argument:
(curry #'+ 3)
See more in the book.
Yes, this is possible in general with the right functions. For example, here is an example in Racket implementing sum from the Wikipedia page:
#lang racket
(define sum (curry foldr + 0))
Since procedures are not curried by default, it helps to use curry or write your functions in an explicitly curried style. You could abstract over this with a new define macro that uses currying.

Emacs Lisp: difference between (function (lambda ...)) and (lambda ...)?

What is the difference between
(function (lambda ...))
and
(lambda ...)
and
'(lambda ...)
?
It seems three are interchangeable in a lot of cases.
They are pretty interchangeable. The answer is that function enables the lambda to be byte compiled, whereas the other two do not (and are equivalent). Note: this does not mean that function actually byte compile the lambda.
How might one figure that out? A little Emacs lisp introspection provides some clues. To start: C-h f function RET:
function is a special form in 'C
source code'.
(function arg)
Like 'quote', but preferred for
objects which are functions. In byte
compilation, 'function' causes its
argument to be compiled. 'quote'
cannot do that.
Ok, so that's the difference between (function (lambda ...)) and '(lambda ...), the first tells the byte compiler that it may safely compile the expression. Whereas the 'ed expressions may not necessarily be compiled (for they might just be a list of numbers.
What about just the bare (lambda ...)? C-h f lambda RET shows:
lambda is a Lisp macro in `subr.el'.
(lambda args [docstring] [interactive]
body)
Return a lambda expression. A call of
the form (lambda args docstring
interactive body) is self-quoting; the
result of evaluating the lambda
expression is the expression itself.
The lambda expression may then be
treated as a function, i.e., stored as
the function value of a symbol, passed
to 'funcall' or 'mapcar', etc.
Therefore, (lambda ...) and '(lambda ...) are equivalent.
Also, there is the notation #'(lambda ...), which is syntactic sugar for (function (lambda ...)).
For more information on functions in Emacs lisp, read the Functions info pages.
Just to check all this, you can type the following into the *scratch* buffer and evaluate the expressions:
(caddr '(lambda (x) (+ x x)))
(+ x x)
(caddr (lambda (x) (+ x x)))
(+ x x)
(caddr (function (lambda (x) (+ x x))))
(+ x x)
(equal '(lambda (x) (+ x x))
(function (lambda (x) (+ x x))))
t
(equal '(lambda (x) (+ x x))
(lambda (x) (+ x x)))
t
So, all three variants of using lambda just build up lists that may be used as functions (one of which may be byte compiled).
Well (quote (lambda...)) and (lambda...) are not equivalent (when byte compiling). Quoted lambdas are not byte compiled whereas everything else is.
For example:
(defun foo (a)
(byte-code-function-p a))
(defun bar ()
(foo '(lambda () (ignore 'me))))
(defun bar2 ()
(foo (lambda () (ignore 'me))))
(defun bar3 ()
(foo (function (lambda () (ignore 'me)))))
(defun bar4 ()
(foo #'(lambda () (ignore 'me))))
(byte-compile 'bar)
(byte-compile 'bar2)
(byte-compile 'bar3)
(byte-compile 'bar4)
(bar) ; -> nil
(bar2) ; -> t
(bar3) ; -> t
(bar4) ; -> t
You usually don't want to quote a lambda unless the function you are going to pass the lambda to is doing something else with it than just funcall it.