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

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.

Related

Defining a type on a list that begins with a particular symbol

I am trying to use generic functions' ability to specify behaviour based on the first argument of a list.
In other words, I want the list (atypelist 1 2 3) and the list (btypelist 1 2 3) to have their individual behaviour when passed to foo. So far, this is what I came up with:
(deftype atypelist (lst)
`(eq (car ,lst) 'atypelist))
(deftype btypelist (lst)
`(eq (car ,lst) 'btypelist))
(defmethod foo ((lst atypelist))
(format nil "success atypelist: ~S" lst))
(defmethod foo ((lst btypelist))
(format nil "success btypelist: ~S" lst))
However, when I call (typep (list 'atypelist 1 2 3) 'atypelist) I get the following error:
error while parsing arguments to DEFTYPE ATYPELIST:
too few elements in
()
to satisfy lambda list
(LST):
exactly 1 expected, but got 0
I am guessing the error is in my definition of atypelist.
Questions:
Is there a better way to get the functionality I am looking for?
If yes - what is the way?
If not - how to properly define a type on a list/cons that has a particular symbol in the car?
Before I start: what you want to do can't work, and is confused in two ways.
Firstly deftype defines a type in terms of other type specifiers: the body of a deftype form must expand into a type specifier, not an expression, as yours does. And deftype's arguments are not the thing you want to check the type for, they are parts of the type specification.
In this case you want to specify that the thing is a cons, and that its car is eql to something. Fortunately there are specializing type specifiers for both of these things, and you end up with something like this:
(deftype cons-with-specified-car (x)
`(cons (eql ,x) t))
And now
> (typep '(1) '(cons-with-specified-car 1))
t
> (typep '(a) '(cons-with-specified-car a))
t
> (typep '() '(cons-with-specified-car a))
nil
And if you want:
(deftype cons-with-a ()
'(cons-with-specified-car a))
and now
> (typep '(a) 'cons-with-a)
t
Secondly none of this will work because this it not how CLOS works. CLOS dispatches on classes not types, and you have merely defined a type, not a class: your method definitions simply cannot work, since classes cannot be parametrized in this way like types can.
Some ways you might achieve what you want.
If what you want to do is to dispatch on the first element of a list, then the obvious approach, if you want to use CLOS, is to use a two-level approach where you first dispatch on the class of the thing (cons is a class), and then use eql specializers to pick out the things you want.
(defgeneric select (it)
(:method ((it cons))
(select* (car it) it))
(:method (it)
nil))
(defgeneric select* (key it)
(:method (key it)
(format t "~&unknown key ~S in ~S~%" key it)))
(defmethod select* ((key (eql 'a)) it)
(format t "~&~S begins with a~%" it))
However in a case like this, unless you very much want the extensibility that CLOS gets you (which is a good reason to use CLOS here), I'd just use typecase. You could do this using the type defined above:
(defun select (it)
(typecase it
((cons-with-specified-car a)
'(cons a))
(cons
'cons)
(t
nil)))
or, probably simpler, just use what the deftype expands into:
(defun select (it)
(typecase it
((cons (eql a) t)
'(cons a))
(cons
'cons)
(t
nil)))
Finally probably what anyone doing this would actually write (again, assuming you do not want the extensibility CLOS gets you) is:
(defun select (it)
(typecase it
(cons
(case (car it)
...))
(t
...)))
Here is a possible solution, using the type specifier satisfies:
CL-USER> (defun is-atypelist (list)
(eq (car list) 'atypelist))
IS-ATYPELIST
CL-USER> (defun is-btypelist (list)
(eq (car list) 'btypelist))
IS-BTYPELIST
CL-USER> (deftype atypelist ()
`(satisfies is-atypelist))
ATYPELIST
CL-USER> (deftype btypelist ()
`(satisfies is-btypelist))
BTYPELIST
CL-USER> (typep (list 'atypelist 1 2 3) 'atypelist)
T
CL-USER> (typep (list 'atypelist 1 2 3) 'btypelist)
NIL
Note that this does not define a class, but a type, if this is what you need.
Is there a better way to get the functionality I am looking for?
1. Wrap your lists in container types
(defclass lst () ((items :initarg :items :reader items)))
(defclass alst (lst) ())
(defclass blst (lst) ())
It may be a little bit more cumbersome to work with but this is pretty much straightforward and not too suprising.
2. Douple-dispatch
(defgeneric foo (val))
(defgeneric foo/tag (tag val))
For example:
(defmethod foo ((c cons))
(destructuring-bind (tag . list) c
(foo/tag tag list)))
3. Define a custom method combination
It should be possible to hack the meta-object protocol dispatch mechanism to dispatch on the first item of a list. I wouldn't recommend it however.
4. Use a different dispatch mechanism
Use a completely different dispatching mechanism outside of CLOS, like pprint-dispatch does. For example you may want to use trivia or optima pattern-matching libraries, or cl-algebraic-data-type. This may be more useful if you are dealing with trees of symbols.

using a struct as property list to macro

I have a struct with :name and :value that I'd like to use as arguments to a macro. But I'm not sure how to tell lisp that.
I can write out the call like
(sxql:yield (sxql:set= :name "a" :value 1))
"SET name = ?, value = ?"
("a" 1)
But I'd like to use an already existing structure
(defstruct my-struct name value)
(setq x (make-my-struct :name "a" :value 1))
; #S(MY-STRUCT :NAME "a" :VALUE 1)
using answers from Common LISP: convert (unknown) struct object to plist?
I've made
(defun struct-plist (x)
"make struct X into a property list. ugly kludge"
(let* ((slots (sb-mop:class-slots (class-of x)))
(names (mapcar 'sb-mop:slot-definition-name slots)))
(alexandria:flatten
(mapcar (lambda (n) (list (intern (string n) "KEYWORD")
(slot-value x n)))
names))))
(setq p (struct-plist x)) ; (:NAME "a" :VALUE 1)
My naive attempts are
(sxql:set= p) ; error in FORMAT: No more argument SET ~{~A = ~A~^, ~}
(funcall 'sxql:set= p) ; SXQL:SET= is a macro, not a function.
(macroexpand (sxql:set= p)) ; error in FORMAT ...
I imagine this is an easy/fundamental lisp programming question. But I'm not sure how to ask it (or search for answers). I'm also hoping there is an better struct<->plist story than what I've stumbled across so far.
EDIT: In case this is really an xy-problem. I've used flydata:defmodel to create the struct and I want to insert to a database using the same model.
This is definitely an xy problem: unfortunately I don't understand y (flydata?) well enough to answer the y part.
Here's why what you are trying to do can't work however. Consider this code in a file being compiled:
(defstruct mine name value)
...
(sxql:set= <anything derived from mine>)
Compiling this file must satisfy two constraints:
It does not fully create the structure type mine (see defstruct);
It must macroexpand sxql:set=.
What these constraints mean is that sxql:set= can't know about the structure at the time it is expanded. So any trick which relies on information about the structure must make that information available at compile time.
As I said, I don't understand the y part well enough to understand what you are trying to do, but a hacky approach to this is:
write a wrapper for defstruct which stashes information at compile time (strictly: at macro-expansion time);
write a wrapper for sxql:set= which uses that information to expand into something which makes sense.
Here is a mindless wrapper for defstruct. Note that this is mindless: it can only understand the most simple defstruct forms, and even then it may be wrong. It exists only as an example.
(eval-when (:compile-toplevel :load-toplevel :execute)
(defvar *structure-information* '()))
(defmacro define-mindless-structure (name &body slots)
(assert (and (symbolp name)
(every #'symbolp slots))
(name slots)
"I am too mindless")
(let ((found (or (assoc name *structure-information*)
(car (push (list name) *structure-information*)))))
(setf (cdr found) (mapcar (lambda (slot)
(list slot (intern (symbol-name slot)
(find-package "KEYWORD"))
(intern (concatenate 'string
(symbol-name name)
"-"
(symbol-name slot)))))
slots)))
`(defstruct ,name ,#slots))
So now
(define-mindless-structure mine
name value)
Will expand into (defstruct mine name value) and, at macroexpansion time will stash some information about this structure in *structure-information*.
Now I stop really understanding what you need to do because I don't know what sxql:set= is meant to do, but it might be something like this:
(defmacro mindless-set= ((s o))
(let ((info (assoc s *structure-information*))
(ov (make-symbol "O")))
(unless info
(error "no information for ~A" s))
`(let ((,ov ,o))
(sxql:set= ,#(loop for (slot initarg accessor) in (cdr info)
;; the compiler will whine about slot annoyingly
collect initarg
collect `(,accessor ,ov))))))
So with this macro, assuming a suitable define-mindless-structure for mine form has been seen by the time the macro is expanded, then
(mindless-set= (mine it))
Will expand into
(let ((#:o it))
(set= :name (mine-name #:o) :value (mine-value #:o)))
But, as I said, I am not sure what the expansion you actually want is.
Finally, before even thinking about using anything like the above, it would be worth looking around to see if there are portability libraries which provide compile/macroexpansion-time functionality like this: there very well may be such, as I don't keep up with things.

Using a quoted list of slots for Peter Seibel's defclass macro

I am using the defclass macro from Practical Common Lisp, which takes as argument a list of symbols.
I would like to change the macro in order to let it accept a quoted list of symbols. This has the benefit of having thenm defined as constants that can be used in other convenience functions, e.g. here. I confused myself in trying to get this done.
My use case is following:
(defconstant state-slots '(unit motion mode moc-offset woc-pos woc-inc feed spindle))
;; would like to use the quoted list here:
(defclass-by-slots gc-state (unit ; :mm(=G21) :inch(=G20)
motor ; nil :on
motion ; :jog(=G0) :lin(=G1) :cw(=G2) :ccw(=G3)
mode ; :abs(=G90) :inc(=G91)
moc-offset ; woc-zero(xyz, mm) from moc-zero
woc-pos ; woc-pos(xyz, mm) from woc-zero
woc-inc
feed
spindle))
;; can use quoted slot list when using a convenience function, e.g:
(defun format-by-slots (o slots &optional str-type)
(let* ((f (lambda (s$) (eval (format-slot o s$))))
(str-type (string-upcase str-type))
(r (concatenate
'string
(format nil "~A (~A)" o (class-of o))
(reduce (lambda (s1 s2) (concatenate 'string s1 s2))
(loop for s in slots
when (funcall f s) collect it)
:from-end t :initial-value (format nil "~%")))))
(if str-type
(ppcre:regex-replace-all
(format nil "^#<~A \\{(\\d|[A-F])+\\}> " str-type)
r
(format nil "#<~A {...}> " str-type))
r)))
I am using this for several classes defined by different slots.
The nuisance is that I cannot have defined the slots uniformly for the type definition and the convenience functions which is source of annoying errors.
Solution based on [Rainer Joswig's answer] (https://stackoverflow.com/a/61154538/2336738):
(defmacro def-my-class (name supers slots-symbol)
"The value of a symbol of slots-symbol is used as the
list of slots."
`(defclass ,name ,supers
,(if (and (symbolp slots-symbol)
(symbol-value slots-symbol)
(listp (symbol-value slots-symbol)))
(mapcar #'slot->defclass-slot (symbol-value slots-symbol))
(error "~a is not a symbol which names a list of slot names" slots-symbol))))
Symbol values at compile time
If you want to use the value of a symbol at compile time, then you need to make sure that it is defined. Two usual ways to do that:
define the symbol in a file and load it before compiling another file where it is used
use EVAL-WHEN to execute a symbol definition (defvar, defparameter,defconstant` ...) at compile time
Read-time evaluation
One possibility to use a symbol value during compilation is to use read-time evaluation. You would need to make sure that the constant value of +state-slots+ is defined during compilation:
(eval-when (:compile-toplevel :load-toplevel :execute)
(defconstant +state-slots+
'(unit motion mode moc-offset woc-pos woc-inc feed spindle)))
(defclass foo ()
#.+state-slots+)
Custom Macro
If the value of +state-slots+ is defined at compile time, then we can also use it in a macro:
(defmacro def-my-class (name supers slots-symbol)
"The value of a symbol of slots-symbol is used as the
list of slots."
`(defclass ,name ,supers
,(if (and (symbolp slots-symbol)
(symbol-value slots-symbol)
(listp (symbol-value slots-symbol)))
(symbol-value slots-symbol)
(error "~a is not a symbol which names a list of slot names"))))
(def-my-class foo () +state-slots+)

Testing if a Variable Contains a Function in Common Lisp

I am writing a common lisp program and I have a variable that can contain either a string or a function. I want to call the function if it is one and return that as well as the string. How do I test if a variable is a function?
Code so far:
(defun string-or-function (var)
(if (typep var 'simple-array)
var
(if "Function equivalent of typep goes here."
(setf temp (fn-that-does-something))
(string-or-function temp)
Edit: Code that works:
(defun string-or-function (var)
(let ((s-or-f (type-of var)))
(if (equal s-or-f 'function)
(print "function")
(if (equal (car s-or-f) 'simple-array)
(print "string")))))
Is there a better way to do it?
Common Lisp has a predicative type system. The notion that a value has a "principal" type doesn't make as much sense in Lisp. The type-of function is actually fairly infrequently used, as it makes less sense to ask "What is the type of X" and more sense to ask "Is X of type Y". This can be done with typep, or in your case more concisely with typecase, which is just a case statement for types.
(defun string-or-function (var)
(typecase var
(string (format t "string"))
(function (format t "function"))
(t (format t "something else"))))
I want to call the function if it is one and return that as well as the string.
I think you mean something like this:
(defun evaluate (arg)
"Returns something from evaluating ARG in some manner. If ARG is a string,
return it. If ARG is a function, call it with no arguments and return its
return value(s)."
(ctypecase arg
(string arg)
(function (funcall arg))))
If you need extensibility:
(defgeneric evaluate (arg)
(:documentation "Returns something from evaluating ARG in some manner."))
(defmethod evaluate ((arg string))
arg)
(defmethod evaluate ((arg function))
(funcall arg))
Here are some other ways:
(defun string-or-function-p (x)
(typep x '(or string function)))
...but you can probably also use check-type, which is not a predicate but a check which signals a restartable condition in case the value does not satisfy the type specification:
(check-type place (or string function))
If you happen to use this type a lot, define a custom type:
(deftype string-or-fun () '(or string function))
Of course, you can also use generic functions depending on your needs (silly example):
(defgeneric execute (object)
(:method ((s string)) (eval (read-from-string s)))
(:method ((f function)) (funcall f)))
But note that generic function dispatch on classes, not types, which are different things.
(eq (type-of var) 'function)
However, remember that Common Lisp keeps variables and function names in different namespaces, so (var 1 2 3) and (cons var 1) are looking in two different places. You probably cannot call var like (var), but will rather need to use (funcall var), depending on which namespace this is in.
Basically, you probably shouldn't be stuffing a function-or-maybe-a-string into one variable.

Common lisp: Redefine an existing function within a scope?

In Common Lisp, is it possible to redefine an already defined function within a certain scope? For example, given a function A that calls a function B. Can I temporarily redefine B during a call to A?
I'm looking for something along the lines of a let block, but that can redefine functions.
Within a given lexical scope, yes. Use FLET or LABELS. Any function defined with FLET will be unable to call functions defined in the same lexical scope, if you want that (for, say, self-recursive of a group of mutually recursive functions), you will need to use LABELS.
Note that both FLET and LABELS only establish lexical shadowing, should not be used to shadow functions from the COMMON-LISP package and will not dynamically change what function is called from outside the lexical scope the form establishes.
Local functions can be introduced with FLET and LABELS.
If you want to redefine/shadow an existing function using dynamic scope, this is a macro I've been using for a while.
(defmacro! with-shadow ((fname fun) &body body)
"Shadow the function named fname with fun
Any call to fname within body will use fun, instead of the default function for fname.
This macro is intentionally unhygienic:
fun-orig is the anaphor, and can be used in body to access the shadowed function"
`(let ((fun-orig))
(cond ((fboundp ',fname)
(setf fun-orig (symbol-function ',fname))
(setf (symbol-function ',fname) ,fun)
(unwind-protect (progn ,#body)
(setf (symbol-function ',fname) fun-orig)))
(t
(setf (symbol-function ',fname) ,fun)
(unwind-protect (progn ,#body)
(fmakunbound ',fname))))))
Usage:
Clozure Common Lisp Version 1.9-r15759 (DarwinX8664) Port: 4005 Pid: 4728
; SWANK 2012-03-06
CL-USER>
(defun print-using-another-fname (x)
(print x))
PRINT-USING-ANOTHER-FNAME
CL-USER>
(let ((*warn-if-redefine-kernel* nil))
(with-shadow (print (lambda (x)
(funcall fun-orig (+ x 5))))
(print-using-another-fname 10)))
15
15
CL-USER>
(print 10)
10
10
CL-USER>
Note that it relies on Doug Hoyte's defmacro! macro, available in Let Over Lambda.
Also as written, it's anaphoric (fun-orig is available within the body). If you want it completely hygienic, just change the fun-orig's to ,g!fun-orig's.
I most often redefine functions when writing unit tests. Mocking functions within the scope of a particular unit test is helpful, and sometimes that needs to be done with dynamic (not lexical) scope.
You can simulate dynamic-binding for funs like this:
(defmacro setvfun (symbol function)
`(progn
(setf ,symbol ,function)
(setf (symbol-function ',symbol) (lambda (&rest args) (apply (symbol-value ',symbol) args)))))
and then ,for example, with
(setvfun some-fun (lambda() (format t "initial-definition~%")))
(defun test-the-fun (&rest args) (apply #'some-fun args))
(defun test ()
(test-the-fun)
(flet ((some-fun () (format t "Lexically REDEFINED (if you see this, something is very wrong)~%")))
(test-the-fun))
(let ((some-fun (lambda (x) (format t "Dynamically REDEFINED with args: ~a~%" x))))
(declare (special some-fun))
(test-the-fun "Hello"))
(test-the-fun))
you get:
REPL> (test)
==>initial-definition
==>initial-definition
==>Dynamically REDEFINED with args: Hello
==>initial-definition

Resources