Why does (find-if #'consp '('notdefinedsymbol)) => 'NOTDEFINEDSYMBOL? - common-lisp

This code came from the emacs buffer slime-repl sbcl :
CL-USER> (consp 'notdefinedsymbol)
NIL
CL-USER> (find-if #'consp '('notdefinedsymbol))
'NOTDEFINEDSYMBOL
If consp returns nil then why does find-if act as if consp returns a true value?

With (consp 'notdefinedsymbol) consp in operator position is a symbol for the #'consp function and thus it's argument (quote notdefinedsymbol), abbrevated as just 'notdefinedsymbol needs to be evaluated before application. A (quote x) evalues to the data x so in our case the argument becomes the symbol notdefinedsymbol. It is NOT a cons but a symbolp and thus the result is nil
With the second you have (find-if #'consp '('notdefinedsymbol)) and since find-if is a fucntion it evaluates its arguments. #'consp evaluates to the function object and '('notdefinedsymbol) which is short for (quote ((quote notdefinedsymbol))) is evaluates. As always it evaluated to its argument which is ((quote notdefinedsymbol)). It is a list with one element which itself is a list with two elements, the symbols quote and notdefinedsymbol. Since (consp '(quote notdefinedsymbol) ; ==> t find-if evaluates to (quote notdefinedsymbol) and some CL printers will abbreviate a list of two elements where the first element is quote with the same manner as the reader macro and print 'notdefinedsymbol but it still is a list of two elements since it is not code, but data.
Your mistake is of course that you nest quotes. If you had done it like this you get your expected result:
(find-if #'consp '(notdefinedsymbol)) ; ==> nil

(consp 'a) - function arguments get evaluated first. So we have: 'a evaluates to: a. And that is an atom, thus NIL.
(find-if #'consp '('a)) also evluates arguments first. But for the first argument of the list, it tests whether 'a is a cons. It is, because that is (quote a) (only the outer ' of the list is evaluated, the inner in front of a not, therefore 'a.
a = notdefinedsymbol.

Your call: (find-if #'consp '('not-defined-symbol)) is the same as (i. e. is expanded by the reader to) (find-if (function consp) (quote ((quote not-defined-symbol)))). The argument (quote ((quote not-defined-symbol))) is evaluated to the list ((quote not-defined-symbol)) (i. e. a list containing a list containing the two symbols quote and not-defined-symbol). Find-if goes through that outer list, tests the inner, which is a cons, with consp, which says true, and returns it.
What you wanted to do is most likely: (find-if #'consp '(not-defined-symbol)), which is the same as (find-if (function consp) (quote (not-defined-symbol)). Note: no nested quote.
Look at the docs for quote and the CLHS chapter about evaluation for a better understanding.

Related

Controlling the printing of special cons forms (e.g printing (function +) as #'+ etc)

I want some reader macros to print as as shortened expression that the macro understands. Lets say I want to extend the #' macro to take #'~[rest-of-symbol] and turn that into (complement #'rest-of-symbol).
What controls how that is printed? On SBCL, for instance, '(function +) prints as #'+. How do i make '(complement #'listp) print as #~listp?
My first thought was
(defmethod print-object :around ((obj cons) stream)
;; if #'~fn-name / (complement (function fn-name))
;; => fn-name otherwise NIL
(let ((fn-name
(ignore-errors
(destructuring-bind (complement (function fn-name))
obj
(when (and (eq complement 'complement)
(eq function 'function))
fn-name)))))
(if fn-name
(format stream "#'~~~S" fn-name)
(call-next-method))))
This works insofar as (print-object '(complement #'evenp) *standard-output*) prints it the way I want, but the REPL doesn't. Also (print-object '#'+ *standard-output*) prints it as (function +) so the REPL isn't using print-object. With defining the print-object method for user defined classes the REPL always picks up on the new definition.
This is my first post and I'm sorry I can't get the code to format properly. If someone can put a link on how to do that I would appreciate it.
Evaluation time
You are mixing code with data in your example:
(function +)
Is a special form that evaluates to a function object, which admits a shorter syntax:
#'+
But when you are writing:
'(function +)
or
'(complement fn)
Then in both cases you are writing quoted, literal lists, which evaluates to themselves (namely a list starting with symbol function or complement, followed respectively by symbol + and fn).
However, you want the code to be evaluated at runtime to actual function objects; if you type this in the REPL:
(complement #'alpha-char-p)
The result is a value that is printed as follows:
#<FUNCTION (LAMBDA (&REST SB-IMPL::ARGUMENTS) :IN COMPLEMENT) {101AAC8D9B}>
You have an actual function object that you can funcall. In other words, by the time you reach print-object, you no longer have access to source code, you are manipulating data at runtime which happens to be functions. So you cannot use destructuring-bind to get the complement symbol that was present in the source code.
What you need to do instead is to attach metadata to your function. There is a way to do that in Common Lisp by defining a new type of function, thanks to the Meta-Object Protocol.
Funcallable objects
I'm relying on Closer-MOP for all the symbols prefixed with c2cl: below. I define a new class of functions, annotated-fn, which is a function with addditional data:
(defclass annotated-fn (c2cl:funcallable-standard-object)
((data :initform :data :initarg :data :reader annotated-fn-data))
(:metaclass c2cl:funcallable-standard-class))
Notice that this class is a funcallable-standard-object (like the usual functions), and its metaclass is funcallable-standard-class. Such an object has an additional implicit slot that is a function to call.
More precisely, you have to call c2cl:set-funcallable-instance-function to set a function associated with the object, and when later you use funcall or apply with the object, then the wrapped function is called instead. So you can transparently use this class of functions wherever you usually use a function. It just has additional slots (here data).
For example, here is how I instantiate it, with a function to wrap additional data:
(defun annotate-fn (function data)
(let ((object (make-instance 'annotated-fn :data data)))
(prog1 object
(c2cl:set-funcallable-instance-function object function))))
Let's try it:
(describe
(annotate-fn (constantly 3)
'(:category :constantly)))
#<ANNOTATED-FN {1006275C7B}>
[funcallable-instance]
Lambda-list: UNKNOWN
Derived type: FUNCTION
Documentation:
T
Source file: SYS:SRC;CODE;FUNUTILS.LISP
Slots with :INSTANCE allocation:
DATA = (:CATEGORY :CONSTANTLY)
You can also use this object like any other function.
Now, your reader macros can expand into calls to annotate-fn, and add any kind of additional metadata you need to the function.
Reader macro
For our example, imagine you define a reader macros for constant functions:
(set-macro-character #\[ 'read-constantly t)
(set-macro-character #\] (get-macro-character #\) nil))
(defun read-constantly (stream char)
(declare (ignore char))
(let* ((list (read-delimited-list #\] stream t))
(value (if (rest list) list (first list)))
(var (gensym)))
`(let ((,var ,value))
(annotate-fn (constantly ,var)
(list :category :constantly
:constant ,var)))))
Using this syntax:
> [(+ 8 5)]
=> #<ANNOTATED-FN ...>
By the way, the syntax I defined also allows the following:
> [+ 8 5]
Pretty-printing
Let's define a generic function that prints an annotated function given its :category field:
(defgeneric print-for-category (category data object stream))
(defmethod print-object ((o annotated-fn) s)
(let* ((data (annotated-fn-data o))
(category (getf data :category)))
(print-for-category category data o s)))
Then, we can specialize it for :constantly, and here we assume also that the data associated with the function contains a :constant field:
(defmethod print-for-category ((_ (eql :constantly)) data o s)
(format s "[~s]" (getf data :constant)))
For example:
(let ((value (+ 8 6)))
(annotate-fn (constantly value)
`(:constant ,value
:category :constantly)))
This above is printed as:
[14]
Which would be the same as your hypothetical reader macro.
To do this you need to understand the pretty printer. I have understood it in the past but no longer do completely. It dispatches on type and the trick for things like this is that you can specify very specific types for trees of conses, although doing so is verbose.
Here is an example which is almost certainly not completely correct, but does achieve what you want in this case:
(defparameter *ppd* (copy-pprint-dispatch))
(defun pprint-complement-function (s form)
;; This is the thing that the pretty printer will call. It can
;; assume that the form it wants to print is already correct.
(destructuring-bind (complement (function name)) form
(declare (ignore complement function))
(format s "#'~~~W" name)))
;;; Now set this in the table with a suitable hairy type specification
;;;
(set-pprint-dispatch '(cons (eql complement)
(cons (cons (eql function)
(cons t null))
null))
'pprint-complement-function
0
*ppd*)
And now
> (let ((*print-pprint-dispatch* *ppd*))
(pprint '(complement (function foo)))
(pprint '((complement (function foo)) (function foo))))
#'~foo
(#'~foo #'foo)
You can make the awful nested cons type specifier easier by defining this (which, perhaps, should be the compound type specifier for list except you can't do that):
(deftype list-of-types (&rest types)
(labels ((lot (tt)
(if (null tt)
'null
`(cons ,(first tt) ,(lot (rest tt))))))
(lot types)))
And then
(set-pprint-dispatch '(list-of-types (eql complement)
(list-of-types (eql function)
*))
'pprint-complement-function
0
*ppd*)
is perhaps easier to read.

Subtle Compiler Warning in SBCL When Compiling a Lambda Expression

I'd like some help with understanding an SBCL compiler warning message, which occurs when compiling a lambda expression. The lambda expression is temporarily stored as the symbol-value of a user-defined name, and the compiled function is subsequently stored under the name's symbol-function.
* (compile nil (symbol-value 'activate-connector-if!))
; in: LAMBDA (STATE ?CONNECTOR)
; (APPLY #'SOME
; (LAMBDA (WOULDWORK-PKG::?T1 WOULDWORK-PKG::?T2)
; (AND
; (GETHASH (+ 126 # #)
; (WOULDWORK-PKG::PROBLEM-STATE.IDB WOULDWORK-PKG::STATE))
; (GETHASH (+ 126 # #)
; (WOULDWORK-PKG::PROBLEM-STATE.IDB WOULDWORK-PKG::STATE))
; (LET (#)
; (WHEN VALUES #))
; (LET (#)
; (WHEN VALUES #))
; (NOT (EQL WOULDWORK-PKG::$HUE1 WOULDWORK-PKG::$HUE2))))
; NIL NIL)
; --> MULTIPLE-VALUE-CALL SB-C::%FUNCALL SOME LET BLOCK SB-INT:DX-FLET FLET
; --> #:WRAPPER102 BLOCK LET
; ==>
; (SB-C::%FUNCALL #:G100 #:G99)
;
; caught WARNING:
; function called with one argument, but wants exactly two
; See also:
; The ANSI Standard, Section 3.2.2.3
;
; compilation unit finished
; caught 1 WARNING condition
#<FUNCTION (LAMBDA (STATE ?CONNECTOR)) {1002E32AAB}>
T
T
The warning corresponds to the two required arguments, but there is no information about where the function is being called from. However, there is only one possible place it can be called from, and a check verifies that it is being called with two arguments.
Since the program runs fine on all test cases in spite of this warning, at first I thought it meant the function is never being called. But a trace verifies it is being called properly a number of times with the correct arguments.
Is there any other way to get at what is generating the warning?
(LAMBDA (WOULDWORK-PKG::?T1 WOULDWORK-PKG::?T2) ...) requires 2 arguments, but it's being called with just 1 argument by SOME. When you convert the APPLY call to a normal function call, it looks like:
(some (lambda (?t1 ?t2) ...) '())
There need to be as many sequence arguments as arguments to the predicate function, but there's only one sequence and two arguments.
Maybe you meant to use FUNCALL rather than APPLY? APPLY treats its last argument as a list of arguments, so NIL is spread into no arguments.

Adding "not" to each item in a sequence in Clojure

I am trying to add (not(X)) to all my items X in a sequence.
For example:
Convert (a b) to
( (not(a)) (not(b)) )
When I use (map (fn [x] (not(x))) mylist), it tries to evaluate the nots and return booleans.
When I use (map (fn [x] '(not(x))) mylist), it just returns a list of (not(x)) without actually putting in my list's variables.
(a b) --> ( (not(a)) (not(b)) ) ? Thanks!
user=> (map (fn [x] (list 'not (list x))) '(a b))
((not (a)) (not (b)))
The ' single quote operator is convenient for making lists because it prevents evaluation, but it isn't usable in your case because you have content inside the resulting list that you want to be evaluated.
Another option would have been ` AKA quasiquote, which allows selective unquoting, but also namespaces symbols (once again, not useful in your case, where you want the symbol used literally).
You can make it more readable and get rid of numerous list calls
by using syntax-quote reader macro:
user> (map (fn [x] `(~'not (~x))) '(a b))
((not (a)) (not (b)))
(see clojure reader documentation's section on [syntax quoting](
http://clojure.org/reader))
unquote-quote not (~'not) is used here to insert literal not symbol instead of namespace-prefixed clojure.core/not

Lisp: How to MAPCAR "#x" over a list of HEX?

Using #x... like below one obtains the decimal of hex value
> #xB1
177
> #xA5
165
> #xFF
255
Say we have a list of hex, what is the correct syntax using mapcar #x... over the list? Below doesn't work:
> (mapcar #'(lambda (hex) `(#x,hex)) '(B1 A5 FF))
Reader error: Malformed number in a #b/#o/#x/#r macro.
[Condition of type SIMPLE-ERROR]
Thanks.
The #x is what's called a "reader macro". It is very similar to using quotations (ie "") to represent strings. They are executed when the code is read/compiled. What you actually want is a procedure which can convert from hexadecimal strings at run time. The procedure you are looking for is parse-integer, which takes a string and returns the value it represents. The mapcar with it should look something like this:
(mapcar (lambda (hex)
(parse-integer hex :radix 16))
'("B1" "A5" "FF"))
Note that this is using strings, if you want to use symbols as in your suggestion you would have to do something like this:
(mapcar (lambda (hex)
(parse-integer (symbol-name hex) :radix 16))
'(B1 A5 FF))
If you don't know the difference between a symbol and a string, I would suggest reading this: What exactly is a symbol in lisp/scheme?
It occurs to me that while the best solution for this problem is probably one using parse-integer as mentioned in malisper's answer, there is a sense in which this could be solved with a mapping based approach.
When we write something like #xB1, we're not explicitly invoking a function. Instead, we're using the fact that # is a dispatching read macro character, and that there's a function installed for the subcharacter x that reads numbers written in hexadecimal. That means that by the time the evaluator or compiler gets a form, the number is already there. However, we do have access to the function that is doing the processing of the hexadecimal string, using get-dispatch-macro-character. Viz.:
CL-USER> (get-dispatch-macro-character #\# #\x)
#<FUNCTION SB-IMPL::SHARP-X> ; in SBCL
CL-USER> (get-dispatch-macro-character #\# #\x)
#<SYSTEM-FUNCTION SYSTEM::HEXADECIMAL-READER> ; in CLISP
What can we do with that function? How would we use it?
2.1.4.4 Macro Characters
… If a character is a dispatching macro character C1, its reader macro
function is a function supplied by the implementation. This function
reads decimal digit characters until a non-digit C2 is read. If any
digits were read, they are converted into a corresponding integer
infix parameter P; otherwise, the infix parameter P is nil. The
terminating non-digit C2 is a character (sometimes called a
``sub-character'' to emphasize its subordinate role in the
dispatching) that is looked up in the dispatch table associated with
the dispatching macro character C1. The reader macro function
associated with the sub-character C2 is invoked with three arguments:
the stream, the sub-character C2, and the infix parameter P. For more
information about dispatch characters, see the function
set-dispatch-macro-character.
That means that when we write something like #xB1, the function above is getting called with a stream from which it can read B1, the character x, and nil. We can try calling that function with arguments like that, although we can't be quite sure what will happen, because implementations might make different assumptions about where the function will be called from.
For instance, this works without a problem in CLISP, but SBCL assumes that the function should be called recursively from read (which we're not doing):
CL-USER> (funcall (get-dispatch-macro-character #\# #\x)
(make-string-input-stream "B1")
#\x
nil)
177 ; in CLISP
CL-USER> (funcall (get-dispatch-macro-character #\# #\x)
(make-string-input-stream "B1")
#\x
nil)
; Evaluation aborted on #<SB-INT:SIMPLE-READER-ERROR "~A was invoked
; with RECURSIVE-P being true outside of a recursive read operation."
; {1005F245B3}>. ; in SBCL
That said, for implementations where this will work, we can easily write a mapcar-like function to extract a dispatch macro character function and map it over some strings. Thus, in an implementation where this works:
(defun map-dispatch-macro-character (disp-char
sub-char
list
&optional (readtable *readtable*))
"Retrieve the dispatch macro character for DISP-CHAR and SUB-CHAR and
map it over the elements in LIST. Each element in LIST is either a
string designator or a two-element list of a string-designator and a
prefix argument."
(flet ((to-list (x)
(if (listp x) x
(list x))))
(let ((fn (get-dispatch-macro-character disp-char sub-char readtable)))
(mapcar (lambda (x)
(destructuring-bind (str &optional prefix) (to-list x)
(with-input-from-string (in (string str))
(funcall fn in sub-char prefix))))
list))))
CL-USER> (map-dispatch-macro-character #\# #\x '(B1 "A5" (FF nil)))
(177 165 255)
And of course, if you really want to be able to write #x, you could of course define a version that just extracts the characters from a string of length two, so that you could do:
CL-USER> (map-dispatch-macro-character* "#x" '(B1 A5 FF))
(177 165 255)

how understand :print-function in defstruct of common lisp

I am reading the book successful lisp, There is a example:
(defstruct (ship
(:print-function
(lambda (struct stream depth)
(declare (ignore depth))
(format stream "[ship ~A of ~A at (~D, ~D) moving (~D, ~D)]"
(ship-name struct)
(ship-player struct)
(ship-x-pos struct)
(ship-y-pos struct)
(ship-x-vel struct)
(ship-y-vel struct)))))
(name "unnamed")
player
(x-pos 0.0)
(y-pos 0.0)
(x-vel 0.0)
(y-vel 0.0))
How can i understand this part:
(lambda (struct stream depth)
(declare (ignore depth))
why declare to ignore the depth? I feel quite confused, why not write lambda as
(lambda (struct stream)
.....)
Thanks
You cannot simply ignore arguments in Common Lisp - unlike, for example, javascript. That is, if you write a function such as
(defun foo (bar baz)
(list bar baz))
you cannot call it with any other number of arguments:
(foo 'a 'b) ; correct number of arguments
=> (a b)
(foo 'a) ; too few arguments
=> error
(foo 'a 'b 'c) ; too many arguments
=> error
As the printer functions are called with three arguments - the object, stream and depth - you must also define all printers with exactly three arguments. The declaration simply removes a warning message by indicating to the compiler you are intentionally leaving the parameter unused.
The Common Lisp standard says this:
If the :print-function option is used, then when a structure of type
structure-name is to be printed, the designated printer function is
called on three arguments:
the structure to be printed (a generalized instance of structure-name).
a stream to print to.
an integer indicating the current depth. The magnitude of this integer may vary between
implementations; however, it can reliably be compared against
*print-level* to determine whether depth abbreviation is appropriate.
So it is a three argument function. We need to write a function which takes three arguments then.
As usual, if our code does not use all arguments, we can declare them to be ignored, so that the compiler will not print a warning. Here the user has not used the variable depth.
Example: in the following function it is not clear if we forgot to use b or if not using it is on purpose.
CL-USER 21 > (defun foo (a b)
(list a))
FOO
CL-USER 22 > (compile 'foo)
;;;*** Warning in FOO: B is bound but not referenced
FOO
Now we can tell the compiler that we chose not to use b.
CL-USER 23 > (defun foo (a b)
(declare (ignore b))
(list a))
FOO
No warnings during compilation:
CL-USER 24 > (compile 'foo)
FOO
NIL
NIL

Resources