read's recursive-p argument when used inside a reader macro - common-lisp

I have written a Common Lisp implementation of Scheme's s-expression comments (SRFI 62):
(eval-when (:compile-toplevel
:load-toplevel
:execute)
(set-dispatch-macro-character #\# #\;
(lambda (stream char n)
(declare (ignore char))
(when n
(error "Infix parameter not allowed in s-expression comment."))
(read stream) ; Discard the s-expression.
(values))))
Based on my reading of The RECURSIVE-P argument, it appears that my implementation is incorrect. I have to use (read stream t nil t) instead (i.e. set the recursive-p argument to t). Is my understanding correct?
I have been using the apparently incorrect implementation above, and it seems to function correctly. What would happen if I continue to use (read stream) instead of (read stream t nil t)?

For an example of incorrect behavior, let's consider the first of the three reasons given in the RECURSIVE-P argument documentation. First, using your original definition:
* (+ 1 #1=2 #;(+ #1# 3))
Reader error: Missing #1# label.
Changing (read stream) into (read string t nil t) gives the correct result:
* (+ 1 #1=2 #;(+ #1# 3))
3

Related

Define a constant array of struct known at compilation-time

In my program I have constant strings, the values are known at compilation time. For each offset there are currently 2 associated strings. I first wrote the following code:
(eval-when (:compile-toplevel :load-toplevel :execute) ;; BLOCK-1
(defstruct test-struct
str-1
str-2))
(eval-when (:compile-toplevel) ;; BLOCK-2
(defparameter +GLOBAL-VECTOR-CONSTANT+ nil) ;; ITEM-1
(let ((vector (make-array 10
:initial-element (make-test-struct)
:element-type 'test-struct)))
(setf (test-struct-str-1 (aref vector 0)) "test-0-1")
(setf (test-struct-str-2 (aref vector 0)) "test-0-2")
(setf +GLOBAL-VECTOR-CONSTANT+ vector)))
(format t "[~A]~%" (test-struct-str-1 (elt +GLOBAL-VECTOR-CONSTANT+ 0)))
(format t "[~A]~%" (test-struct-str-2 (elt +GLOBAL-VECTOR-CONSTANT+ 0)))
This seems to work as it returns the following:
[test-2-1]
[test-2-2]
In BLOCK-1 the struct containing the data is defined, for compile-time, load-time and execute-time. In BLOCK-2, the code which create a vector and sets the values is executed, at compile-time.
But I have the following concerns:
This code seems unnecessary verbose
The strings are stored in a structure
I need to manually set the offset of each values ((aref vector 0), (aref vector 1), etc).
When I set ITEM-1 inside BLOCK-1 instead of BLOCK-2 I get an error in SBCL which I don't understand
What is the idiomatic way to define complex constants in Common Lisp?
It's not really clear what you want to do from your question.
First important note: your code is seriously broken. It's broken because you define +global-vector-constant+ only at compile time but refer to it later than that. If you compile this file and then load that compiled file into a cold image you will get errors.
It is absolutely critical when dealing with things like this to make sure that your code will compile in a cold Lisp. One of the classic problems with resident environments (which CL isn't really, compared to the way Interlisp-D was for instance) is to end up with systems which you can't cold build: I'm pretty sure I worked for several years with an Interlisp-D sysout that no-one knew how to cold build any more.
If what you want is an object (an array, for instance) whose initial value is computed at compile time and then treated as a literal, then the answer to that is, in general, a macro: macros are exactly functions which do their work at compile time, and so a macro can expand to a literal. In addition it must be the case that the object you want to be a literal is externalizable (which means 'can be dumped in compiled files') and anything involved in it is known about at compile time. Instances of some classes are externalizable by default, those of some other classes can be made externalizable by user code, and some are not externalizable at all (for instance functions).
In quite a lot of simple cases, like the one you gave, if I understand it, you don't really need a macro, and in fact you can almost always get away without one, although it may make your code easier to understand if you do use one.
Here is a simple case: many arrays are externalizable if their elements are
(defparameter *my-strings*
#(("0-l" . "0-r")
("1-l" . "1-r")))
This means that *my-strings* will be bound to a literal array of conses of strings.
A more interesting case is when the elements are, for instance structures. Well, structures are also externalizable, so we can do that. And in fact it's quite possible, still, to avoid a macro, although it now becomes a bit noisy.
(eval-when (:compile-toplevel :load-toplevel :execute)
(defstruct foo
l
r))
(defparameter *my-strings*
#(#s(foo :l "0-l" :r "0-r")
#s(foo :l "1-l" :r "1-r")))
Note that the following won't work:
(defstruct foo
l
r)
(defparameter *my-strings*
#(#s(foo :l "0-l" :r "0-r")
#s(foo :l "1-l" :r "1-r")))
It won't work because, at compile time, you are trying to externalize instances of a structure which is not yet defined (but it probably will work if the Lisp is not cold, and you might even be able to reload the compiled file you made that way). Again, in this case you can avoid the eval-when in a larger system by ensuring that the file which defines the foo structure is compiled and loaded before the file with the defparameter is loaded.
And even in more complex cases you can escape using a macro. For instance for many sorts of objects which are normally not externalizable you can teach the system how to externalize them, and then splice the object in as a literal using #.:
(eval-when (:compile-toplevel :load-toplevel :execute)
;; Again, this would be in its own file in a bigger system
(defclass string-table-wrapper ()
((strings)
(nstrings :initform 0)))
(defmethod initialize-instance :after ((w string-table-wrapper)
&key (strings '()))
(let ((l (length strings)))
(when l
(with-slots ((s strings) (n nstrings)) w
(setf s (make-array l :initial-contents strings)
n l)))))
(defmethod make-load-form ((w string-table-wrapper) &optional environment)
(make-load-form-saving-slots w :slot-names '(strings nstrings)
:environment environment))
) ;eval-when
(defgeneric get-string (from n)
(:method ((from string-table-wrapper) (n fixnum))
(with-slots (strings nstrings) from
(assert (< -1 n nstrings )
(n)
"bad index")
(aref strings n))))
(defparameter *my-strings*
#.(make-instance 'string-table-wrapper
:strings '("foo" "bar")))
Note that, of course, although the value of *my-strings* is a literal, code ran to reconstruct this object at load-time. But that is always the case: it's just that in this case you had to define what code needed to run. Instead of using make-load-form-saving-slots you could have done this yourself, for instance by something like this:
(defmethod make-load-form ((w string-table-wrapper) &optional environment)
(declare (ignore environment))
(if (slot-boundp w 'strings)
(values
`(make-instance ',(class-of w))
`(setf (slot-value ,w 'strings)
',(slot-value w 'strings)
(slot-value ,w 'nstrings)
,(slot-value w 'nstrtrings)))
`(make-instance ',(class-of w))))
But make-load-form-saving-slots is much easier.
Here is an example where a macro does perhaps least make reading the code easier.
Let's assume you have a function which reads an array of strings from a file, for instance this:
(defun file-lines->svector (file)
;; Needs CL-PPCRE
(with-open-file (in file)
(loop
with ltw = (load-time-value
(create-scanner '(:alternation
(:sequence
:start-anchor
(:greedy-repetition 1 nil
:whitespace-char-class))
(:sequence
(:greedy-repetition 1 nil
:whitespace-char-class)
:end-anchor)))
t)
for nlines upfrom 0
for line = (read-line in nil)
while line
collect (regex-replace-all ltw line "") into lines
finally (return (make-array nlines :initial-contents lines)))))
Then, if this function is available at macroexpansion time, you could write this macro:
(defmacro file-strings-literal (file)
(check-type file (or string pathname) "pathname designator")
(file-lines->svector file))
And now we can create a literal vector of strings:
(defparameter *fl* (file-strings-literal "/tmp/x"))
However you could perfectly well instead do this:
(defparameter *fl* #.(file-lines->svector "/tmp/x"))
Which will do the same thing, but slightly earlier (at read time, rather than at macroexpansion/compile time). So this is gaining nothing really.
But you could also do this:
(defmacro define-stringtable (name file &optional (doc nil docp))
`(defparameter ,name ,(file-lines->svector file)
,#(if docp (list doc) nil)))
And now your code reads like
(define-stringtable *st* "my-stringtable.dat")
And that actually is a significant improvement.
Finally note that in file-lines->svector that load-time-value is used to create the scanner exactly once, at load time, which is a related trick.
First of all, your let code can be simplified to
(defparameter +global-vector-constant+
(let ((vector ...))
...
vector))
Second, you can also do
(defparameter +global-vector-constant+
(make-array 10 :element-type 'test-struct :initial-content
(cons (make-test-struct :str-1 "test-0-1" :str-2 "test-0-2")
(loop :repeat 9 :collect (make-test-struct)))))
Note that the benefit of :element-type 'test-struct is generally limited to code self-documentation (see upgraded-array-element-type)

Macro reader for #+

I'm trying to write a formatting program for Common Lisp code, for which I need to tweak the behavior of the reader, e.g. with a reader macro for comments. Currently looking at #+ e.g.
(defun args ()
#+CCL CCL:*UNPROCESSED-COMMAND-LINE-ARGUMENTS*
#+SBCL (cdr *posix-argv*))
Default reader behavior is to discard the currently inactive branch entirely, but for my purposes I need to keep both. I think that means I need a reader macro for #+.
But # is also a prefix to lots of other things. How can I write a reader macro that handles #+ while keeping the default behavior for # everything else?
The # character is a dispatch macro character, meaning you can define a reader macro for the #+ combination without affecting any other reader macros beginning with hash.
You can start from the code below, and customize it to do what you want it to:
;; define the reader function
(defun custom-comment-reader-macro (stream char &optional num)
;; char will be #\+ in our case, and num will be nil.
;; stream will be the code input stream
(declare (ignore char num))
;; this is the default behaviour of #+, you can customize it below
(if (member (intern (string (read stream)) :keyword)
*features*)
(read stream)
(progn (read stream) ;ignore next token
(values)))) ;return nothing
;; tell the reader to use our function when it encounters #+
(set-dispatch-macro-character #\# #\+ #'custom-comment-reader-macro)

HANDLER-CASE alternative which is not a macro

So consider the following code:
(define-condition some-condition (error) nil)
(defmethod print-object ((obj some-condition) stream)
(format stream "HELLO THERE"))
(defmacro error-report-test-aux (fn-to-cause-error error-type-to-catch fn-to-handle-error expected-message)
`(let ((result-message
(handler-case (funcall ,fn-to-cause-error)
(,error-type-to-catch (e) (funcall ,fn-to-handle-error e)))))
(assert (string= result-message
,expected-message))
t))
I can use it like so:
(error-report-test-aux (lambda () (error 'some-condition))
some-condition
#'princ-to-string
"HELLO THERE")
But I wanted to make error-report-test-aux a function instead of macro, so that i can pass to it a type of condition within a variable.
To simply write defun instead of defmacro and remove backquote and commas doesn't work because handler-case is macro and it doesn't evaluate error-type-to-catch.
My question is: Is there something like handler-case that would evaluate it's arguments (specifically condition type argument)?
Yes and no :-)
No to your exact question
There is no standard function that would do what you want because catching errors requires establishing bindings and one usually want to bind constant symbols (like in let/let*) because it is easier to optimize.
You might consider creating a "universal" handler using handler-bind and then declining to handle "uninteresting" conditions (as suggested by #jkiiski in comments), but I am not sure if that fits your exact requirements (untested!):
(defun error-report-test-aux (fn-to-cause-error error-type-to-catch expected-message)
(catch 'trap
(handler-bind ((error
(lambda (condition)
(when (typep condition error-type-to-catch)
(throw 'trap (string= (princ-to-string condition)
expected-message))))))
(funcall fn-to-cause-error))))
Yes, implementation-specific
IF your implementation implements handler-case/handler-bind by binding an internal global variable, you can use progv to bind it yourself and thus implement your error-report-test-aux as a function.
This is probably not the best idea (your code becomes wedded to a specific implementation).
Yes, kinda
You can use the fact that some-condition names a CLOS class and use generic functions instead of the macro.

Not null lexical environment for eval

How to evaluate some lisp code using eval in not null lexical environment ? I need this feature for proper interpolation functionality.
If you model your environment as bindings like those found in let:
((x 3) (y 2))
... then you can evaluate any form f with those bindings in place, like so:
(eval `(let ,e ,f))
This is the simplest case, but you can easily convert your data to fit this syntax. You can also bind functions, macros, etc. if needed.
Note that if you need values at runtime, then maybe dynamic bindings are better. You can use hash-tables, etc. but note that there is also the lesser-known PROGV special operator:
Among other things, progv is useful when writing interpreters for languages embedded in Lisp; it provides a handle on the mechanism for binding dynamic variables.
Although I think the OP knows the answer already, let me try to give a somewhat more descriptive solution, hoping more experienced lispers can point to mistakes I may make below:
As #coredump mentions, progv is an option as well as a let form in eval. Here is an example:
Let's create a list with some numbers and a cons that has a lambda form, bypassing the reader lambda conversion:
(setf list1 '(1
1
(lambda ()
(print a))))
we can eval:
(eval
`(let ((a 3))
;; statement after comma is turned to a function by the reader.
;; same effect with explicit (funcall (function ,(third list1)))
;; because of the (lambda ..) macro form
(funcall ,(third list1))))
3
3
Note that variable a above is lexical, not special.
now, with progv we can create special variables and eval will use them.
Let's first start with a mistake:
(progv '(a) '(4)
(funcall (function (third list1))))
Error: (THIRD LIST1) is not a valid argument for FUNCTION.
or similarly:
(progv '(a) '(4)
(funcall (third list1)))
Error: Argument to apply/funcall is not a function: (LAMBDA NIL (PRINT A)).
Then, let's evaluate or compile:
(progv '(a) '(4)
(funcall (eval (third list1))))
4
4
or
(progv '(a) '(4)
(funcall (compile nil (third list1))))
Warning in 246: A assumed special
4
4
Above is the behaviour I got with LispWorks 7.1. eval didn't give the warning for special assumption, because:
(eval (third list1))
#<anonymous interpreted function 40600009EC>
eval returned an interpreted function, not compiled. If we further compile, then we'll see the same warning:
(eval (third list1))
#<anonymous interpreted function 40600009EC>
(compile nil *)
;;;*** Warning in 248: A assumed special
To make things right with progv, since it creates special variables, change the function:
(setf list1 '(1
1
(lambda ()
(declare (special a))
(print a))))
(progv '(a) '(4)
(funcall (compile nil (third list1))))
4
4
Note that to make the example politically correct, as CLHS does in progv page, we should better use (progv '(*a*) '(4) ...) and the lambda function should be defined with the *a* variable.

In Common Lisp, how to test if variable is special?

I thought I would be able to find this through Google, SO, or the books I'm reading, but it is proving elusive.
In the implementation I'm learning with, I can do the following at the top-level:
(defvar *foo* 4)
(set 'bar 3)
If I then call (describe '*foo*) and (describe 'bar), I get a description saying that *foo* is special and bar is non-special (among other details).
Is there a function that takes a symbol variable as an argument and returns true or false if it is special? If so, is describe probably implemented in part by calling it?
Context: I'm learning Common Lisp, but at work I have a system with a dialect of Lisp similar to Common Lisp, but the describe function is unimplemented. There's sort of an XY thing going on here, but I'm also trying to grok Lisp and CL.
Many Common Lisp implementations provide the function variable-information in some system dependent package.
Here in SBCL:
* (require :sb-cltl2)
NIL
* (sb-cltl2:variable-information '*standard-output*)
:SPECIAL
NIL
((TYPE . STREAM))
This function was proposed as part of some other functionality to be included into ANSI CL, but didn't make it into the standard. Still many implementations have it. For documentation see: https://www.cs.cmu.edu/Groups/AI/html/cltl/clm/node102.html
A non-special variable's environment will be captured when you create a closure over it:
(let ((x 1))
(let ((f (lambda () x)))
(let ((x 2))
(eql 2 (funcall f)))))
;;=> NIL
A special variable's lexical environment will not:
(defvar *x*) ; *x* is special
(let ((*x* 1))
(let ((f (lambda () *x*)))
(let ((*x* 2))
(eql 2 (funcall f)))))
;;=> T
Using this approach, you could easily define a macro that will expand to code like the previous that will let you determine whether a symbol is globally proclaimed special:
(defmacro specialp (symbol)
(let ((f (gensym "FUNC-")))
`(let ((,symbol 1))
(let ((,f (lambda () ,symbol)))
(let ((,symbol 2))
(eql 2 (funcall ,f)))))))
(specialp x) ;=> NIL
(specialp *x*) ;=> T
Note that this isn't a function, it's a macro. That means that the macro function for specialp is getting called with the symbols X and *X*. This is important, because we have to construct code that uses these symbols. You can't do this with a function, because there'd be no (portable) way to take a symbol and create a lexical environment that has a lexical variable with that name and a lambda function that refers to it.
This also has some risks if you try to use it with certain symbols. For instance, in SBCL, if you try to bind, e.g., *standard-output* to something that isn't a stream or a stream designator, you'll get an error:
CL-USER> (specialp *standard-output*)
; in: SPECIALP *STANDARD-OUTPUT*
; (LET ((*STANDARD-OUTPUT* 1))
; (LET ((#:FUNC-1038 (LAMBDA # *STANDARD-OUTPUT*)))
; (LET ((*STANDARD-OUTPUT* 2))
; (EQL 2 (FUNCALL #:FUNC-1038)))))
;
; caught WARNING:
; Constant 1 conflicts with its asserted type STREAM.
; See also:
; The SBCL Manual, Node "Handling of Types"
;
; compilation unit finished
; caught 1 WARNING condition
Defining globals with set or setq is not supported. There are 2 common ways to define globals:
(defparameter *par* 20) ; notice the earmuffs in the name!
(defvar *var* 30) ; notice the earmuffs in the name!
All global variables are special. Lexically scoped variables (not special) are not possible to get described. E.g.
(let ((x 10))
(describe 'x)) ; ==> X is the symbol X
It describes not the lexical variable but the symbol representation. It really doesn't matter since you probably never need to know in run time since you know this when you're writing if it's a bound lexical variable or global special by conforming to the earmuffs naming convention for global variables.
I believe the only way to get this information at run time* is by either using an extension to CL, as Rainer noted, or to use eval.
(defun specialp (x)
(or (boundp x)
(eval `(let (,x)
(declare (ignorable ,x))
(boundp ',x)))))
(Defect warning: If the variable is unbound but declared to be a type incompatible with nil, this could raise an error. Thanks Joshua for pointing it out in his answer.)
* The macro approach determines which symbol it is checking at macro expansion time, and whether that symbol is lexical or special at compile time. That's fine for checking the status of a variable at the repl. If you wanted to e.g. print all of the special variables exported by a package, though, you would find that to use the macro version you would end up having to use eval at the call site:
(loop for s being the external-symbols of :cl-ppcre
when (eval `(specialp-macro ,s)) do (print s))

Resources