This is a macro defined in "clx-user-callable.lisp" I'm trying to use.
(in-package :clx-gui)
(defmacro get-callback-wrapper (callback)
(declare (ignorable callback))
(let* ((func-name (gensym))
(wrapper-name (intern (format nil "WRAPPER-~a" func-name) )))
`(defun ,wrapper-name (caller-instance)
(funcall ,callback) ;; User callbacks wont have arguments
(closemenu caller-instance))))
I call this macro in this manner and it works properly.
(in-package :clx-gui-test-app)
(create-user-menuitem "MyUserMenu" "MyEntryDialog"
(get-callback-wrapper 'my-callback))
(create-user-menuitem "MyUserMenu" "MyChoiceDialog"
(get-callback-wrapper 'my-callback2))
(create-user-menuitem "MyUserMenu" "MyMessageDialog"
(get-callback-wrapper 'my-callback3))
If I change the code to use the macro this way, by passing the symbol name of the callback to a function that calls the macro, it does not return different wrapper functions, but always returns the same wrapper function. The function that calls the macro is in the same file and package as the macro definition.
(in-package :clx-gui-test-app)
(create-user-menuitem "MyUserMenu" "MyEntryDialog" 'my-callback)
(create-user-menuitem "MyUserMenu" "MyChoiceDialog" 'my-callback2)
(create-user-menuitem "MyUserMenu" "MyMessageDialog" 'my-callback3)
I have tried adding the package to the macro definition, but that doesn't help.
(wrapper-name (intern (format nil "WRAPPER-~a" func-name)
(symbol-package callback) )))
What am I doing incorrectly?
I'm working with SBCL-1.0.57 and Slime.
CL-USER>
(defparameter foo1 (gensym))
FOO1
CL-USER>
foo1
#:G4619
CL-USER>
(defparameter foo2 '#:G4619)
FOO2
CL-USER>
foo2
#:G4619
CL-USER>
(eq foo1 foo2)
NIL
CL-USER>
~
Or another fun exercise:
(defmacro make-fun ()
`(defun ,(intern (format nil "WRAPPER-~a" (gensym))) ()
'bar))
CL-USER>
(make-fun)
WRAPPER-G4726
CL-USER>
(make-fun)
WRAPPER-G4730
CL-USER>
(make-fun)
WRAPPER-G4734
CL-USER>
(make-fun)
WRAPPER-G4738
CL-USER>
(defun WRAPPER-G4745 ()
'foo)
WRAPPER-G4745
CL-USER>
(make-fun)
WRAPPER-G4745
CL-USER> (wrapper-G4745)
BAR
CL-USER>
Oh man, we just wrote over that function!
If you want to notate a gensym with some sort of prefix name, do it in the gensym call (as an optional argument). But all of this is just an exercise, b/c I would still just use lambda in the OP problem.
Here's an alternative implementation that is (IMO) simpler, and should work for your needs:
(defun get-callback-wrapper (callback)
(lambda (caller-instance)
(funcall callback)
(closemenu caller-instance)))
This generates the lexical closure that I think you're after.
Related
When working in a top level REPL, I sometimes forget what definitions I've entered into the running lisp system.
I use Clozure CL and it provides the option of saving the application as an image, which I do and can continue where I left off, but at this point it becomes impossible to review all the code, unless I had separately typed and saved the code to xyz file already.
Is there a way to get/extract/view the definitions that I entered, so I can save them as a source file?
The following will extract all the function definitions entered in a package:
(defun get-all-symbols (&optional package)
(let ((lst nil)
(package (find-package package)) )
(do-all-symbols (s lst)
(when (fboundp s)
(unless (and package (not (eql (symbol-package s) package)))
(push (cons s (function-lambda-expression s)) lst) )))))
Try something like:
(get-all-symbols *package*)
Common Lisp (in general) does not provide any standard way to “recover” the source code of a definition once it has been compiled. Normally, it's found in whatever file or buffer you're working-from.
(As Leo's answer points out, there is Function-Lambda-Expression, which can give you some function definitions. It won't help with, say, constants or classes, and it won't always work — as CLHS says, “Any implementation may legitimately return nil as the lambda-expression of any function.” http://clhs.lisp.se/Body/f_fn_lam.htm — his solution is certainly useful in the most common case(s), but it is not “as general” as this one.)
You could use a set of “wrapper” macros which store the forms you pass to them in a global hash-table, and then recover the source from that. Writing that sounded like an interesting little challenge, so the below is my attempt to do something like that.
My Silly Wrappers Solution
Note that the “source” forms stashed in this way won't preserve reader macros, comments, or the like, and will probably choke on some things like defmethod in subtly horrible ways. That's because I blindly store the definitions keyed off the defining form — eg, defun — and the second word, only. It's not smart enough to notice if you rebound a function as a macro or generic function (all three conflicting definitions would be saved), it doesn't read method combinations or lambda lists to save various methods, or any of that. There are lots of other things you might do — eg, (SetF (FDefinition 'FOO) …) — that could bypass these and go unnoticed, so it's far from “foolproof.” Caveat Lector.
The macros here try to inherit the documentation and lambda lists from the underlying forms, so they should work pretty nicely with most IDE's. They do well enough, in Slime.
One way to work with these would be to directly call them; eg, in your REPL you could directly
My-Package> (use-package :wrap-defining-form)
My-Package> (defun$ my-fn (x) (+ x (sqrt x)))
A more dangerous/interesting way is provided in the package Wrap-Defining-Form.Shadowing, in which the macros shadow the real Common-Lisp package definitions …
CL-User> (in-package :CL-USER$)
CL-User$> (defun blah (n) (loop repeat n do (format t "~&Blah …")))
When you're ready to “save” things, run (dump-definitions).
I wrote and tested this in SBCL, but tried to take care that it should work on many/most other implementations. In particular, I used one non-ANSI function: SB-Introspect:Function-Lambda-List. The function here Wrap-Defining-Form::Find-Function-Lambda-List will search all packages for your implementation's version of that function. If it can't find one, all is not lost; but you won't get hints from your IDE about the lambda-list of the wrapped function. (Clozure's seems to work — kinda — for functions, but not macros. That can probably be improved.)
CL-USER> (describe 'defun$)
WRAP-DEFINING-FORM:DEFUN$
[symbol]
DEFUN$ names a macro:
Lambda-list: (NAME LAMBDA-LIST &BODY BODY)
Documentation:
Wrap `DEFUN' and save the original form.
DEFUN: Define a function at top level.
Source file: /home/brpocock/Private/wrap-defining-form.lisp
; No value
Without Function-Lambda-List, the wrapper looks like
Lambda-list: (&REST UNKNOWN-LAMBDA-LIST)
… which is not very helpful.
wrap-defining-form.lisp
EDIT: Debugged in Clozure. Posted to https://github.com/brpocock/wrap-defining-forms also.
;;;; Wrap--Defining-Forms
;;; -*- Lisp -*-
(defpackage wrap-defining-forms
(:use :common-lisp)
(:documentation "Wrap defining forms so that they (try to) save the
source code of the definition being passed.")
(:export #:wrap-defining-form #:dump-definitions
#:defclass$
#:defconstant$
#:defgeneric$
#:define-compiler-macro$
#:define-condition$
#:define-method-combination$
#:define-modify-macro$
#:define-setf-expander$
#:define-symbol-macro$
#:defmacro$
#:defmethod$
#:defpackage$
#:defparameter$
#:defsetf$
#:defstruct$
#:deftype$
#:defun$
#:defvar$))
(defpackage wrap-defining-forms.shadowing
(:documentation "Wrapped forms like DEFUN$ are exported here with the
names of the forms that they wrap, like DEFUN, for
shadowing imports.")
(:export #:defclass
#:defconstant
#:defgeneric
#:define-compiler-macro
#:define-condition
#:define-method-combination
#:define-modify-macro
#:define-setf-expander
#:define-symbol-macro
#:defmacro
#:defmethod
#:defpackage
#:defparameter
#:defsetf
#:defstruct
#:deftype
#:defun
#:defvar)
(:use))
;; Clozure appears to be “smart” and adds Common-Lisp even though we
;; didn't ask for it (and explicily don't want it)
#+ccl (unuse-package '(:ccl :common-lisp)
:wrap-defining-forms.shadowing)
(defpackage :common-lisp-user/save-defs
(:nicknames :cl-user$)
(:use :common-lisp :common-lisp-user)
(:import-from :wrap-defining-forms #:dump-definitions)
(:shadowing-import-from :wrap-defining-forms.shadowing
#:defclass
#:defconstant
#:defgeneric
#:define-compiler-macro
#:define-condition
#:define-method-combination
#:define-modify-macro
#:define-setf-expander
#:define-symbol-macro
#:defmacro
#:defmethod
#:defpackage
#:defparameter
#:defsetf
#:defstruct
#:deftype
#:defun
#:defvar))
;; Clone any other functions you may have packed into CL-User.
(with-package-iterator (next-symbol :common-lisp-user :internal)
(loop for symbol = (next-symbol)
while symbol
for sibling = (intern (symbol-name symbol) (find-package :cl-user$))
when (and (fboundp symbol)
(not (fboundp sibling)))
do (setf (fdefinition sibling) (fdefinition symbol))))
(in-package "WRAP-DEFINING-FORMS")
(defvar *definitions* (make-hash-table)
"Copies of forms defined by the wrappers created by
`WRAP-DEFINING-FORM' which can be stashed with `DUMP-DEFINITIONS'")
#+ccl
(defun ccl-mock-lambda-list (function)
(if (macro-function function)
(list '&rest 'macro-lambda-list)
(multiple-value-bind (required optional restp
keywords)
(ccl:function-args (fdefinition function))
(concatenate ' list
(loop repeat required
collect (gensym "ARG-"))
(when (and optional (plusp optional))
(cons '&optional
(loop repeat optional
collect (gensym "OPT-"))))
(when restp
(list '&rest 'rest))
(when (and keywords (plusp keywords))
(list '&key '&allow-other-keys))))))
(defun find-function-lambda-list ()
"Find the implementation's version of `FUNCTION-LAMBDA-LIST' if there
is one. That way, Slime and friends can still give the proper
lambda-list for the wrapped form. If it can't be found, this will
return a stub with just a &rest-var."
(or
#+sbcl #'sb-introspect:function-lambda-list
#+ccl #'ccl-mock-lambda-list
#-(or ccl sbcl)
(dolist (package (list-all-packages))
(let ((sym (find-symbol "FUNCTION-LAMBDA-LIST" package)))
(when (fboundp sym)
(return-from find-function-lambda-list sym))))
(lambda (function)
(declare (ignore function))
(list '&rest 'unknown-lambda-list))))
(defmacro wrap-defining-form (cl-form)
"Assuming that CL-FORM is a symbol for a macro or function which
defines something interesting (eg, “Defun”), this will create a macro
with the same name with a trailing “$” that will save the source tree
before passing on the form to CL-FORM.
EG: (wrap-defining-form defun) provides a “defun$” which has the
additional side effect of storing the source form in *DEFINITIONS*.
Definitions saved can be recovered by `DUMP-DEFINITIONS'.
This is not industrial-strength; in particular, I expect it to cope
poorly with DEFMETHOD."
(check-type cl-form symbol)
(let ((wrapper (intern (concatenate 'string (symbol-name cl-form) "$")))
(wrapper.shadow (intern (symbol-name cl-form) :wrap-defining-forms.shadowing))
(wrapped-lambda-list (funcall (find-function-lambda-list) 'defun)))
(setf (gethash cl-form *definitions*) (make-hash-table))
`(prog1
(defmacro ,wrapper (&whole whole ,#wrapped-lambda-list)
(declare (ignore ,#(remove-if (lambda (form) (member form lambda-list-keywords))
wrapped-lambda-list)))
,(concatenate 'string "Wrap `" (symbol-name cl-form) "' and save the original form." #(#\newline #\newline)
(symbol-name cl-form) ": " (or (documentation cl-form 'function)
"(see CLHS; no documentation here)"))
(let ((defined (cons ',cl-form (cdr whole))))
(setf (gethash (second whole) (gethash ',cl-form *definitions*))
defined)
defined))
(defmacro ,wrapper.shadow (&whole whole ,#wrapped-lambda-list)
(declare (ignore ,#(remove-if (lambda (form) (member form lambda-list-keywords))
wrapped-lambda-list)))
,(concatenate 'string "Wrap `COMMON-LISP:" (symbol-name cl-form) "' and save the original form."
#(#\newline #\newline)
(symbol-name cl-form) ": " (or (documentation cl-form 'function)
"(see CLHS; no documentation here)"))
(let ((defined (cons ',cl-form (cdr whole))))
(setf (gethash (second whole) (gethash ',cl-form *definitions*))
defined)
defined)))))
(wrap-defining-form defclass)
(wrap-defining-form defconstant)
(wrap-defining-form defgeneric)
(wrap-defining-form define-compiler-macro)
(wrap-defining-form define-condition)
(wrap-defining-form define-method-combination)
(wrap-defining-form define-modify-macro)
(wrap-defining-form define-setf-expander)
(wrap-defining-form define-symbol-macro)
(wrap-defining-form defmacro)
(wrap-defining-form defmethod)
(wrap-defining-form defpackage)
(wrap-defining-form defparameter)
(wrap-defining-form defsetf)
(wrap-defining-form defstruct)
(wrap-defining-form deftype)
(wrap-defining-form defun)
(wrap-defining-form defvar)
(defun dump-definitions (&optional pathname)
"Write out the definitions saved by `WRAP-DEFINING-FORM'-built
wrappers to PATHNAME (or *STANDARD-OUTPUT*)."
(let (output
(*print-case* :capitalize)
;; If writing to file, set margin at 79, but try to keep things under 72.
(*print-right-margin* (if pathname 79 *print-right-margin*))
(*print-miser-width* (if pathname 72 *print-miser-width*)))
(unwind-protect
(progn (setq output (if pathname
(open pathname :direction :output
:if-exists :rename
:if-does-not-exist :create)
*standard-output*))
(multiple-value-bind (sec min hr d m y) (decode-universal-time (get-universal-time))
(declare (ignore sec))
(format output
"~&~|~%;;; definitions as of ~d-~d-~d # ~d:~2,'0d:
\(In-Package #:~a)
~{~{~2%~:<~W ~#_~:I~W ~:_~W~1I ~_~W~:>~}~^~|~}~%~|~%" ; from CLHS 22.2.2 SIMPLE-PPRINT-DEFUN
y m d hr min
(package-name *package*)
(remove-if #'null
(loop for form being the hash-keys of *definitions*
for defs = (gethash form *definitions*)
collect (loop for definition being the hash-values of defs
collect definition))))))
(when output (ignore-errors (close output))))))
Sample Usage
CL-USER> (load "wrap-defining-form.lisp")
T
CL-USER> (use-package :wrap-defining-form)
T
CL-USER> (defun$ trash-word (word)
(let ((s (string word)))
(sort (remove-if-not #'alpha-char-p s) #'char<)))
WARNING: redefining COMMON-LISP-USER::TRASH-WORD in DEFUN
TRASH-WORD
CL-USER> (trash-word 'Blatherscythe)
"ABCEEHHLRSTTY"
CL-USER> (describe 'trash-word)
COMMON-LISP-USER::TRASH-WORD
[symbol]
TRASH-WORD names a compiled function:
Lambda-list: (WORD)
Derived type: (FUNCTION (T) (VALUES SEQUENCE &OPTIONAL))
Source form:
(SB-INT:NAMED-LAMBDA TRASH-WORD
(WORD)
(BLOCK TRASH-WORD
(LET ((S (STRING WORD)))
(SORT (REMOVE-IF-NOT #'ALPHA-CHAR-P S) #'CHAR<))))
; No value
CL-USER> (macroexpand-1 '(defun$ trash-word (word)
(let ((s (string word)))
(sort (remove-if-not #'alpha-char-p s) #'char<))))
(DEFUN TRASH-WORD (WORD)
(LET ((S (STRING WORD)))
(SORT (REMOVE-IF-NOT #'ALPHA-CHAR-P S) #'CHAR<)))
T
CL-USER> (dump-definitions)
;;; definitions as of 2016-12-1 # 15:23:
(In-Package #:COMMON-LISP-USER)
(Defun Trash-Word (Word)
(Let ((S (String Word)))
(Sort (Remove-If-Not #'Alpha-Char-P S) #'Char<)))
NIL
CL-USER> (in-package :Common-Lisp-User/Save-Defs)
#<PACKAGE "COMMON-LISP-USER/SAVE-DEFS">
CL-USER$> (defun 2+ (n) (+ 2 n))
2+
CL-USER$> (describe '2+)
COMMON-LISP-USER/SAVE-DEFS::2+
[symbol]
2+ names a compiled function:
Lambda-list: (N)
Derived type: (FUNCTION (T) (VALUES NUMBER &OPTIONAL))
Source form:
(SB-INT:NAMED-LAMBDA 2+
(N)
(BLOCK 2+ (+ 2 N)))
; No value
CL-USER$> (macroexpand-1 '(defun 2+ (n) (+ 2 n)))
(COMMON-LISP:DEFUN 2+ (N) (+ 2 N))
T
CL-USER$> (documentation 'defun 'function)
"Wrap `COMMON-LISP:DEFUN' and save the original form.
DEFUN: Define a function at top level."
CL-USER$> (dump-definitions)
;;; definitions as of 2016-12-1 # 15:32:
(In-Package #:COMMON-LISP-USER/SAVE-DEFS)
(Common-Lisp:Defun 2+ (N) (+ 2 N))
(Common-Lisp:Defun Trash-Word (Word)
(Let ((S (String Word)))
(Sort (Remove-If-Not #'Alpha-Char-P S) #'Char<)))
NIL
File Backup
Dump-Definitions also will write to a file. (It sets :If-Exists :Rename, so you could have one-level-UNDO protection as well.)
CL-USER$> (dump-definitions "saved.lisp")
NIL
Here is an interactive session with CCL:
? (declaim (optimize (debug 3)))
NIL
The above is not strictly required here, but it doesn't hurt to develop with high debugging levels.
? (defun foo (x) (+ 3 x))
FOO
? (inspect 'foo)
[0] FOO
[1] Type: SYMBOL
[2] Class: #<BUILT-IN-CLASS SYMBOL>
Function
[3] INTERNAL in package: #<Package "COMMON-LISP-USER">
[4] Print name: "FOO"
[5] Value: #<Unbound>
[6] Function: #<Compiled-function FOO #x3020004B3F7F>
[7] Arglist: (X)
[8] Plist: NIL
Inspect> 6
[0] #<Compiled-function FOO #x3020004B3F7F>
[1] Name: FOO
[2] Arglist (analysis): (X)
[3] Bits: 8388864
[4] Plist: (CCL::PC-SOURCE-MAP #(17 70 15 22) CCL::FUNCTION-SYMBOL-MAP
(#(X) . #(63 17 70)) CCL::%FUNCTION-SOURCE-NOTE ...)
[5] Source Location: #<SOURCE-NOTE Interactive "(defun foo (x) (+ 3 x))">
Inspect 1> 5
[0] #<SOURCE-NOTE Interactive "(defun foo (x) (+ 3 x))">
[1] Type: SOURCE-NOTE
[2] Class: #<STRUCTURE-CLASS SOURCE-NOTE>
[3] SOURCE: #(40 100 101 102 117 ...)
[4] FILENAME: NIL
[5] FILE-RANGE: 23
You can see that even from within the REPL, and without running Slime which might also store information about the Emacs environment, you can have access to the source code of FOO. This can be used if you know which function you want to recover. For a recording of your interactive session, follow jkiiski's advice about DRIBBLE.
Perhaps you can easily implement something like this yourself:
(defun my-repl (&optional (file-path "cl-history.lisp"))
"Saves commands to a file"
(loop
(with-open-file (stream file-path
:direction :output
:if-does-not-exist :create
:if-exists :append)
(print '>)
(let ((input (read)))
(format stream "~A~%" input)
(print (eval input))))))
To exit the inner loop you should type (quit).
Alternatively you can use com.informatimago.common-lisp.interactive.interactive:repl
I'm attempting to write my first anaphoric macro and am running into a problem. I am using sblc and slime.
When the anaphoric macro is expanded in another package its symbols are prefixed with the package it was defined in (i.e. they become tjb-utilities::value instead of just value. What is going on?
PE> (macroexpand-1 '(act-if-key :pcram (get-node) (print value)))
(IF (HAS-KEY? :PCRAM (GET-NODE))
(LET ((TJB-UTILITIES::KEY :PCRAM)
(TJB-UTILITIES::VALUE (GETHASH :PCRAM (GET-NODE))))
(PRINT VALUE)))
This is the macro definition:
(defmacro act-if-key (key hashtable &body body)
`(if (has-key? ,key ,hashtable)
(let ((key ,key) (value (gethash ,key ,hashtable)))
,#body)))
It does work correclty if I prefix the value:
(act-if-key :pcram (get-node) (print tjb-utilities::value))
; in: ACT-IF-KEY :PCRAM
; (LET ((TJB-UTILITIES::KEY :PCRAM)
; (TJB-UTILITIES::VALUE
; (GETHASH :PCRAM (PHILOSOPHY-EXPERIENCE::GET-NODE))))
; (PRINT TJB-UTILITIES::VALUE))
;
; caught STYLE-WARNING:
; The variable TJB-UTILITIES::KEY is defined but never used.
;
; compilation unit finished
; caught 1 STYLE-WARNING condition
"hello"
"hello"
The packages are defined as follows:
(defpackage #:tjb-utilities
(:nicknames :tjb)
(:use #:cl)
(:export "HAS-KEY?" "KEY-VALUE-PAIRS" "ACT-IF-KEY" "TJB-MAKE-HASH-TABLE"))
(defpackage #:my-package
(:nicknames :pe)
(:use #:cl #:clsql #:tjb-utilities))
Update: Changing the key in the lambda list to key_in has no effect
(defmacro act-if-key (key_in hashtable &body body)
`(if (has-key? ,key_in ,hashtable)
(let ((key ,key_in) (value (gethash ,key_in,hashtable)))
,#body)))
You could just export 'key and 'value symbols. That's how Anaphora does it:
(defpackage :anaphora
7 (:use :cl)
8 (:export
9 #:it
10 #:alet
11 #:slet
12 #:aif
13 #:aand
14 #:sor
15 #:awhen
16 #:aprog1
17 #:acase
18 #:aecase
...etc.
Note the 'it export.
The point of an anaphoric macro is to intentionally capture certain symbols in the body of the macro that have not been explicitly defined by the caller of the macro (I understand that this is an extreme stance on the definition). So, it is a requirement for anyone using an anaphoric macro to know what symbols are being introduced into the environment (body) of that macro. Which means that they should not be surprised when those symbol names are added to the environment. So I see no problem with exporting the anaphora.
CL-USER> (in-package #:tjb)
#<PACKAGE "TJB-UTILITIES">
TJB> (defmacro act-if-key (key hashtable &body body)
(let ((value (intern "VALUE")))
`(if (has-key? ,key ,hashtable)
(let ((key ,key) (,value (gethash ,key ,hashtable)))
,#body))))
ACT-IF-KEY
TJB> (macroexpand-1 '(tjb:act-if-key :pcram (get-node) (print value)))
(IF (HAS-KEY? :PCRAM (GET-NODE))
(LET ((KEY :PCRAM) (VALUE (GETHASH :PCRAM (GET-NODE))))
(PRINT VALUE)))
T
TJB> (in-package #:cl-user)
#<PACKAGE "COMMON-LISP-USER">
CL-USER> (macroexpand-1 '(tjb:act-if-key :pcram (get-node) (print value)))
(IF (TJB-UTILITIES::HAS-KEY? :PCRAM (GET-NODE))
(LET ((TJB-UTILITIES::KEY :PCRAM) (VALUE (GETHASH :PCRAM (GET-NODE))))
(PRINT VALUE)))
T
CL-USER>
Not sure if I copied all that you needed, and I'm a tad blur on how did you intend to use the "key", so I did it only for the value in the way it will be created in the package, where the macro is used. You'd figure it for yourself whether you need the same for the key or not.
The above bind the symbol value in the current package to whatever gethash will return. In your original version you have key supplied by the user of the macro, so I decided you didn't want a symbol key inside the macro, just it's value.
But wait a bit, perhaps there will be a better answer, maybe you can just make-symbol it instead of interning and then bind it somehow. I'm not sure.
Here's the thing: I don't "get" setf-expanders and would like to learn how they work.
I need to learn how they work because I've got a problem which seems like a typical example for why you should learn setf-expanders, the problem is as follows:
(defparameter some-array (make-array 10))
(defun arr-index (index-string)
(aref some-array (parse-integer index-string))
(setf (arr-index "2") 7) ;; Error: undefined function (setf arr-index)
How do I write a proper setf-expander for ARR-INDEX?
(defun (setf arr-index) (new-value index-string)
(setf (aref some-array (parse-integer index-string))
new-value))
In Common Lisp a function name can not only be a symbol, but also a list of two symbols with SETF as the first symbol. See above. DEFUN thus can define SETF functions. The name of the function is (setf arr-index).
A setf function can be used in a place form: CLHS: Other compound forms as places.
The new value is the first argument then.
CL-USER 15 > some-array
#(NIL NIL NIL NIL NIL NIL NIL NIL NIL NIL)
CL-USER 16 > (setf (arr-index "2") 7)
7
CL-USER 17 > some-array
#(NIL NIL 7 NIL NIL NIL NIL NIL NIL NIL)
Rainer's answer is spot on. Before ANSI Common Lisp, it was necessary to use defsetf to define an expander for simple places that could be set with a simple function call. setf functions like (setf arr-index) came into the language with CLOS and simplify a lot of things. In particular, setf functions can be generic.
I am putting together a macro to generate simple functions of the style:
(defun hello ()
(format t "hello~&"))
Each new function will have hello replaced.
(defmacro generate-echoers (list)
`(let ((list-of-functions
(loop for var in ,list
collect
`(defun ,(intern var) ()
(format t ,(concatenate var "~&"))))))
`(progn
,list-of-functions)))
I developed the above function, which demonstrates conclusively that I have not yet masted quote-times and phases of expansion.
The desired usage is as follows:
(generate-echoers '("hi" "ping" "pong")) => ;A list of functions that each say their name, as HELLO does above.
A function to generate:
(defun hello ()
(format t "hello~&"))
I would first write a function which creates above code:
(defun make-echoers (name)
`(defun ,(intern (string-upcase name)) ()
(format t ,(concatenate 'string name "~&"))))
Note that symbols are by default uppercase in Common Lisp - so we are using uppercase, too.
Then you can test it:
CL-USER 1 > (make-echoers "hello")
(DEFUN HELLO NIL (FORMAT T "hello~&"))
Works. Now let's use it:
(defmacro generate-echoers (list)
`(progn ,#(mapcar #'make-echoers list)))
Test it:
CL-USER 2 > (macroexpand-1 '(generate-echoers ("hi" "ping" "pong")))
(PROGN
(DEFUN HI NIL (FORMAT T "hi~&"))
(DEFUN PING NIL (FORMAT T "ping~&"))
(DEFUN PONG NIL (FORMAT T "pong~&")))
Your code can be simplified and made more correct like this:
(defmacro generate-echoers (list)
`(progn ,#(loop :for var :in list
:collect `(defun ,(intern (format nil "~:#(~A~)" var)) ()
(format t ,(concatenate 'string var "~&"))))))
First of all, you've got to splice the loop's result into the generated body.
Also you've forgotten, that concatenate takes type parameter and to upcase all your vars (otherwise you'll get function names like |foo|).
If you pass symbols to the generate-echoers macro (instead of strings), the intern call is no longer necessary:
(defmacro generate-echoers (&rest echoers)
`(progn
,#(mapcar (lambda (var)
`(defun ,var ()
(format t ,(format nil "~(~a~)~&" var))))
echoers)))
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