Common Lisp: How to quote parenthese in SBCL - lisp

In Common Lisp, the special operator quote makes whatever followed by un-evaluated, like
(quote a) -> a
(quote {}) -> {}
But why the form (quote ()) gives me nil? I'm using SBCL 1.2.6 and this is what I got in REPL:
CL-USER> (quote ())
NIL
More about this problem: This is some code from PCL Chapter 24
(defun as-keyword (sym)
(intern (string sym) :keyword))
(defun slot->defclass-slot (spec)
(let ((name (first spec)))
`(,name :initarg ,(as-keyword name) :accessor ,name)))
(defmacro define-binary-class (name slots)
`(defclass ,name ()
,(mapcar #'slot->defclass-slot slots)))
When the macro expand for the following code:
(define-binary-class id3-tag
((major-version)))
is
(DEFCLASS ID3-TAG NIL
((MAJOR-VERSION :INITARG :MAJOR-VERSION :ACCESSOR MAJOR-VERSION)))
which is NIL rather than () after the class name ID3-TAG.

nil and () are two ways to express the same concept (the empty list).
Traditionally, nil is used to emphasize the boolean value "false" rather than the empty list, and () is used the other way around.
The Common LISP HyperSpec says:
() ['nil], n. an alternative notation for writing the symbol nil, used
to emphasize the use of nil as an empty list.

Your observation is due to an object to having more than one representation. In Common Lisp the reader (that reads code and reads expressions) parses text to structure and data. When it's data the writer can print it out again but it won't know exactly how the data was represented when it was initially read in. The writer will print one object exactly one way, following defaults and settings, even though there are several representations for that object.
As you noticed nil, NIL, nIL, NiL, ... ,'nil, 'NIL, (), and '() are all read as the very same object. I'm not sure the standard dictates exactly how it's default representation out should be so I guess some implementations choose one of NIL, nil or maybe even ().
With cons the representation is dependent on the cdr being a cons/nil or not:
'(a . nil) ; ==> (a)
'(a . (b . c)) ; ==> (a b . c)
'(a . (b . nil)) ; ==> (a b)
With numbers the reader can get hints about which base you are using. If no base is used in the text it will use whatever *read-base* is:
(let ((*read-base* 2)) ; read numbers as boolean
(read-from-string "(10 #x10)")) ; ==> (2 16)
#x tells the reader to interpret the rest as a hexadecimal value. Now if your print-base would have been 4 the answer to the above would have been visualized as (2 100).
To sum it up.. A single value in Common Lisp may have several good representations and all of them would yield the very same value. How the value is printed will follow both implementation, settings and even arguments to the functions that produce them. Neither what it accepts as values in or the different ways it can visualize the value tells nothing about how the value actually gets stored internally.

Related

What is the difference between #\ , ' and #'?

In Common Lisp, given that "a" is simply a character, what is the difference between #\a, 'a #'a?
My question comes from the tutorialspoint.com tutorial on Lisp. At one point the tutorial introduces:
; a character array with all initial elements set to a
; is a string actually
(write(make-array 10 :element-type 'character :initial-element #\a))
(terpri)
; a two dimensional array with initial values a
(setq myarray (make-array '(2 2) :initial-element 'a :adjustable t))
(write myarray)
(terpri)
With the output:
"aaaaaaaaaa"
#2A((A A) (A A))
#' is not included in this example but I'm including it in the question because it can be confusing as well. 🙂
Thank you very much! 😊
To start, a is not "simply a character." The Lisp reader parses #\a as the character literal a, which is an object in Common Lisp. Note that #\a and #\A are different character objects.
When the Lisp reader encounters a single quote, the expression following the single quote is not evaluated. Specifically, 'a is treated as (quote a), where quote returns its argument unevaluated. Now, a is a symbol, so 'a evaluates to that symbol. But the Lisp reader upcases most characters it reads by default, so 'a really evaluates to the symbol A. The good news is that whether you type a or A, the Lisp reader will read A (unless you mess with the readtable), and both 'a and 'A evaluate to the symbol A.
When the Lisp reader encounters #'a, the entire expression is treated as (function a), which when evaluated returns the function associated with the name a. But, note that it is an error to use function, and by extension #', on an identifier that does not denote a function.
To clarify this last part a bit, consider the following REPL interaction:
CL-USER> (defvar a 1)
A
CL-USER> a
1
CL-USER> #'a
The function COMMON-LISP-USER::A is undefined.
[Condition of type UNDEFINED-FUNCTION]
Here the variable a is defined and given the value 1, but when we try to access the function denoted by a we get an error message because there is no such function. Continuing:
; Evaluation aborted on #<UNDEFINED-FUNCTION A {1002DDC303}>.
CL-USER> (defun a (x) x)
A
CL-USER> (a 'b)
B
CL-USER> a
1
CL-USER> #'a
#<FUNCTION A>
Now we have defined a function named a that simply returns its argument. You can see that when we call a with an argument 'b we get the expected result: (a 'b) --> b. But, then when we evaluate a alone we still get 1. Symbols in Common Lisp are objects that have, among other cells, value cells and function cells. After the above interaction, the symbol a now has 1 in its value cell, and it has the function we have defined in its function cell. When the symbol a is evaluated the value cell is accessed, but when (function a) or #'a is evaluated, the function cell is accessed. You can see above that when #'a is evaluated, the function we defined is returned, and the REPL prints #<FUNCTION A> to show this.
As an aside, I wouldn't recommend using Tutorialspoint to learn Common Lisp. Glancing over the site, right away I see this:
LISP expressions are case-insensitive, cos 45 or COS 45 are same.
This is just wrong. And, Lisp is not written in all-caps. None of this inspires faith. Instead, find a good book. There are some recommendations on the common-lisp tag-info page.
#\
This is to introduce a character.
CL-USER> #\a
#\a
CL-USER> (character 'a)
#\A
CL-USER> (character "a")
#\a
'
This is quote, to quote and not evaluate things and construct object literals.
CL-USER> a
=> error: the variable a is unbound.
CL-USER> 'a
A
CL-USER> (inspect 'a)
The object is a SYMBOL.
0. Name: "A"
1. Package: #<PACKAGE "COMMON-LISP-USER">
2. Value: "unbound"
3. Function: "unbound"
4. Plist: NIL
> q
CL-USER> (equal (list 1 2) (quote (1 2))) ;; aka '(1 2)
T ;; but watch out with object literals constructed with quote, prefer constructor functions.
and #'
This is sharpsign-quote to reference a function.
CL-USER> #'a
=> error: The function COMMON-LISP-USER::A is undefined.
CL-USER> (defun a () (print "hello A"))
A
CL-USER> (a)
"hello A"
"hello A"
CL-USER> #'a
#<FUNCTION A>
CL-USER> (function a)
#<FUNCTION A>
One can ask Lisp to describe the data objects you've mentioned.
If we look at the expressions:
CL-USER 13 > (dolist (object (list '#\a ''a '#'a))
(terpri)
(describe object)
(terpri))
#\a is a CHARACTER
Name "Latin-Small-Letter-A"
Code 97
(QUOTE A) is a LIST
0 QUOTE
1 A
(FUNCTION A) is a LIST
0 FUNCTION
1 A
NIL
If we look at the evaluated expressions:
CL-USER 5 > (dolist (object (list #\a 'a #'a))
(terpri)
(describe object)
(terpri))
#\a is a CHARACTER
Name "Latin-Small-Letter-A"
Code 97
A is a SYMBOL
NAME "A"
VALUE #<unbound value>
FUNCTION #<interpreted function A 422005BD54>
PLIST NIL
PACKAGE #<The COMMON-LISP-USER package, 73/256 internal, 0/4 external>
#<interpreted function A 422005BD54> is a TYPE::INTERPRETED-FUNCTION
CODE (LAMBDA (B)
A)

In common lisp how do you restart where the error was thrown not caught?

This question is really about my lack of understanding of restarts.
In the encoder for cl-json there exists a tempting macro I would like to use
with-substitute-printed-representation-restart
But alas I do not quite understand how.
This
(cl-json::encode-json-plist (list :boo "boo" :foo "foo"))
returns
{"boo":"boo","foo":"foo"}
This
(cl-json::encode-json-plist (list :boo "boo" :foo (lambda (a b) (+ a b))))
signals an UNENCODABLE-VALUE-ERROR
I would like to restart from that point where cl-json finds the function and have it return
something of my choosing when it runs into that adding lambda I included in the list.
(defun my-func ()
(handler-bind ((cl-json::UNENCODABLE-VALUE-ERROR
#'(lambda (e) (invoke-restart 'return-default))))
(myencode (list :boo "boo" :foo (lambda (a b) (+ a b))))
)
)
(defun myencode (alist)
(restart-case
(cl-json::encode-json-plist-to-string alist)
(return-default () :report "Just return a default could not do this string" "barf")
)
)
returns "barf"
I want it to return
{"boo":"boo","foo":"barf"}
How do I use that macro do to this?
In other words I want the restart to happen where the error was thrown not where the error was caught. Can I do that?
I don't understand if the doc is wrong or if I am reading the code badly, but there should already be a restart available whenever an object cannot be encoded. If you redefined cl-json default method for encode-json as follows, then you have a restart.
(defmethod encode-json (anything &optional (stream *json-output*))
"If OBJECT is not handled by any specialized encoder signal an error
which the user can correct by choosing to encode the string which is
the printed representation of the OBJECT."
(with-substitute-printed-representation-restart (anything stream)
(unencodable-value-error anything 'encode-json)))
By the way you could redefine so that the restart accepts an argument, the string to print instead:
(defmethod encode-json (anything &optional (stream *json-output*))
"If OBJECT is not handled by any specialized encoder signal an error
which the user can correct by choosing to encode the string which is
the printed representation of the OBJECT."
(with-substitute-printed-representation-restart (anything stream)
(restart-case (unencodable-value-error anything 'encode-json)
(use-value (v)
:report "Use a different encoding"
(check-type v string)
(write v :stream stream :escape t)))))
For example:
CL-USER> (handler-bind
((json:unencodable-value-error
(lambda (err)
(declare (ignore err))
(invoke-restart 'use-value "UNKNOWN"))))
(json:encode-json
`(((foo . ,#'print) (bar . "baz")))))
[{"foo":"UNKNOWN","bar":"baz"}]
You may want to ask directly the author of the library

Lisp quote work internally

How does lisp quote work internally?
For example:
(quote (+ 1 (* 1 2)) )
seems to be equivalent to
(list '+ 1 (list '* 1 2))
which means it is some how symbolizing the Head values recursively. Is this function a built in?
Run (equal (quote (+ 1 (* 1 2))) (list '+ 1 (list '* 1 2))) if you don't believe me.
How does it work?
quote is really really simple to implement. It does mostly nothing. The quote special operator just returns the enclosed object like it is. Nothing more. No evaluation. The object is not changed in any way.
Evaluation of quoted forms
Probably a good time to read McCarthy, from 1960:
Recursive Functions of Symbolic Expressions and Their Computation by Machine, Part I
Pages 16/17 explain evaluation with eval. Here:
eq [car [e]; QUOTE] → cadr [e];
or in s-expression notation:
(cond
...
((eq (car e) 'quote)
(cadr e))
...)
Above code implements the evaluation rule for QUOTE: If the expression is a list and the first element of the list is the symbol QUOTE, then return the second element of the list.
Equivalence of a quoted list with a list created by LIST
(equal (quote (+ 1 (* 1 2)))
(list '+ 1 (list '* 1 2)))
The result is T. This means that both result lists are structurally equivalent.
(eq (quote (+ 1 (* 1 2)))
(list '+ 1 (list '* 1 2)))
The result is NIL. This means that the first cons cell of the linked lists are not the same objects. EQ tests whether we really have the same cons cell object.
QUOTE returns a literal data object. The consequences of modifying this object is undefined. So, don't do it.
LIST returns a new freshly consed list each time it is called. The fresh new list will not share any cons cells with any earlier allocated list.
So the main difference is that QUOTE is a built-in operator, which returns literal and unevaluated data. Whereas LIST is a function which creates a new,fresh list with its arguments as contents.
See the effects with respect to EQ and EQUAL:
CL-USER 6 >
(flet ((foo () (quote (+ 1 (* 1 2))))
(bar () (list '+ 1 (list '* 1 2))))
(list (list :eq-foo-foo (eq (foo) (foo)))
(list :eq-foo-bar (eq (foo) (bar)))
(list :eq-bar-bar (eq (foo) (bar)))
(list :equal-foo-foo (equal (foo) (foo)))
(list :equal-foo-bar (equal (foo) (bar)))
(list :equal-bar-bar (equal (foo) (bar)))))
((:EQ-FOO-FOO T)
(:EQ-FOO-BAR NIL)
(:EQ-BAR-BAR NIL)
(:EQUAL-FOO-FOO T)
(:EQUAL-FOO-BAR T)
(:EQUAL-BAR-BAR T))
is quote a function?
quote can't be a function, since it returns its enclosed data unevaluated. Thus it is a special evaluation rule.
If quote were a function, it's arguments were evaluated. But that's exactly what is NOT what quote is supposed to do.
why does Lisp need QUOTE?
Lisp usually uses s-expressions to write Lisp code. So s-expressions have a both purpose to denote data and we use it to write programs. In a Lisp program lists are used for function calls, macro forms and special forms. symbols are used as variables:
(+ n 42)
Here (+ n 42) is a list and n is a symbol. But we also want to use lists as data in our programs and we want to use symbols as data. Thus we have to quote them, so that Lisp will not see them as programs, but as data:
(append '(+ n) '(42)) evaluates to (+ n 42)
Thus in a Lisp program, lists and variables are by default part of the language elements, for example as function calls and variables. If we want to use lists and symbols as literal data, we have to quote them, to prevent the evaluator treating them as Lisp code to evaluate.
quote does nothing more than return its argument unevaluated. But what is an unevaluated argument?
When a Lisp program is defined, it is either read from textual source into s-expression form or constructed directly in terms of s-expressions. A macro would be an example of generating s-expressions. Either way there is a data structure comprising (mostly) symbols and conses that represents the program.
Most Lisp expressions will call upon evaluation and compilation machinery to interpret this data structure as terms in a program. quote is treated specially and passed these uninterpreted symbols and conses as its argument. In short, quote does almost nothing - the value it returns already exists and is simply passed through.
You can observe the difference between passing through and fresh construction by using eq to test the identity of the return value of quote:
(defun f () '(1 2))
(defun g () (list 1 2))
(eq (f) (f)) => T
(eq (g) (g)) => NIL
As you can see, quote returns the same conses each time through.

Call several functions with the same value

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.

Treating the values from a list of slots and strings

I want to do a macro in common lisp which is supposed to take in one of its arguments a list made of slots and strings. Here is the prototype :
(defclass time-info ()
((name :initarg name)
(calls :initarg calls)
(second :initarg second)
(consing :initarg consing)
(gc-run-time :initarg gc-run-time)))
(defun print-table (output arg-list time-info-list) ())
The idea is to print a table based on the arg-list which defines its structure. Here is an example of a call to the function:
(print-table *trace-output*
'("|" name "||" calls "|" second "\")
my-time-info-list)
This print a table in ascII on the trace output. The problem, is that I don't know how to explicitely get the elements of the list to use them in the different parts of my macro.
I have no idea how to do this yet, but I'm sure it can be done. Maybe you can help me :)
I would base this on format. The idea is to build a format string
from your arg-list.
I define a helper function for that:
(defun make-format-string-and-args (arg-list)
(let ((symbols ()))
(values (apply #'concatenate 'string
(mapcar (lambda (arg)
(ctypecase arg
(string
(cl-ppcre:regex-replace-all "~" arg "~~"))
(symbol
(push arg symbols)
"~a")))
arg-list))
(nreverse symbols))))
Note that ~ must be doubled in format strings in order to escape them.
The printing macro itself then just produces a mapcar of format:
(defmacro print-table (stream arg-list time-info-list)
(let ((time-info (gensym)))
(multiple-value-bind (format-string arguments)
(make-format-string-and-args arg-list)
`(mapcar (lambda (,time-info)
(format ,stream ,format-string
,#(mapcar (lambda (arg)
(list arg time-info))
arguments)))
,time-info-list)))
You can then call it like this:
(print-table *trace-output*
("|" name "||" calls "|" second "\\")
my-time-info-list)
Please note the following errors in your code:
You need to escape \ in strings.
Second is already a function name exported from the common-lisp
package. You should not clobber that with a generic function.
You need to be more precise with your requirements. Macros and Functions are different things. Arrays and Lists are also different.
We need to iterate over the TIME-INFO-LIST. So that's the first DOLIST.
The table has a description for a line. Each item in the description is either a slot-name or a string. So we iterate over the description. That's the second DOLIST. A string is just printed. A symbol is a slot-name, where we retrieve the slot-value from the current time-info instance.
(defun print-table (stream line-format-description time-info-list)
(dolist (time-info time-info-list)
(terpri stream)
(dolist (slot-or-string line-format-description)
(princ (etypecase slot-or-string
(string slot-or-string)
(symbol (slot-value time-info slot-or-string)))
stream))))
Test:
> (print-table *standard-output*
'("|" name "||" calls "|" second "\\")
(list (make-instance 'time-info
:name "foo"
:calls 100
:second 10)
(make-instance 'time-info
:name "bar"
:calls 20
:second 20)))
|foo||100|10\
|bar||20|20\
First, you probably don't want the quote there, if you're using a macro (you do want it there if you're using a function, however). Second, do you want any padding between your separators and your values? Third, you're probably better off with a function, rather than a macro.
You also seem to be using "array" and "list" interchangeably. They're quite different things in Common Lisp. There are operations that work on generic sequences, but typically you would use one way of iterating over a list and another to iterate over an array.