Improve survived_gc_yet()
[sbcl.git] / src / code / fdefinition.lisp
bloba43eaba5b478b4d5b497a3fc5b244573a590b7dd
1 ;;;; This file contains functions that hack on the global function
2 ;;;; namespace (primarily concerned with SETF functions here). Also,
3 ;;;; function encapsulation and routines that set and return
4 ;;;; definitions disregarding whether they might be encapsulated.
6 ;;;; This software is part of the SBCL system. See the README file for
7 ;;;; more information.
8 ;;;;
9 ;;;; This software is derived from the CMU CL system, which was
10 ;;;; written at Carnegie Mellon University and released into the
11 ;;;; public domain. The software is in the public domain and is
12 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
13 ;;;; files for more information.
15 (in-package "SB!IMPL")
17 (sb!int::/show0 "fdefinition.lisp 22")
19 ;;;; fdefinition (fdefn) objects
21 (defun make-fdefn (name)
22 #!-immobile-space (make-fdefn name)
23 ;; This is %primitive because it needs pseudo-atomic,
24 ;; otherwise it would just be an alien-funcall.
25 #!+immobile-space
26 (let ((fdefn (truly-the (values fdefn)
27 (%primitive sb!vm::alloc-immobile-fdefn name))))
28 (%primitive fdefn-makunbound fdefn)
29 fdefn))
31 (defun fdefn-name (fdefn)
32 (declare (type fdefn fdefn))
33 (fdefn-name fdefn))
35 (defun fdefn-fun (fdefn)
36 (declare (type fdefn fdefn)
37 (values (or function null)))
38 (fdefn-fun fdefn))
40 (defun (setf fdefn-fun) (fun fdefn)
41 (declare (type function fun)
42 (type fdefn fdefn)
43 (values function))
44 #!+immobile-code (sb!vm::%set-fdefn-fun fdefn fun)
45 #!-immobile-code (setf (fdefn-fun fdefn) fun))
47 (defun fdefn-makunbound (fdefn)
48 (declare (type fdefn fdefn))
49 (fdefn-makunbound fdefn))
51 #!-sb-fluid (declaim (inline symbol-fdefn))
52 ;; Return SYMBOL's fdefinition, if any, or NIL. SYMBOL must already
53 ;; have been verified to be a symbol by the caller.
54 (defun symbol-fdefn (symbol)
55 (declare (optimize (safety 0)))
56 (info-vector-fdefn (symbol-info-vector symbol)))
58 ;; Return the fdefn object for NAME, or NIL if there is no fdefn.
59 ;; Signal an error if name isn't valid.
60 ;; Assume that exists-p implies LEGAL-FUN-NAME-P.
62 (declaim (ftype (sfunction ((or symbol list)) (or fdefn null)) find-fdefn))
63 (defun find-fdefn (name)
64 (declare (explicit-check))
65 (when (symbolp name) ; Don't need LEGAL-FUN-NAME-P check
66 (return-from find-fdefn (symbol-fdefn name)))
67 ;; Technically the ALLOW-ATOM argument of NIL isn't needed, but
68 ;; the compiler isn't figuring out not to test SYMBOLP twice in a row.
69 (with-globaldb-name (key1 key2 nil) name
70 :hairy
71 ;; INFO-GETHASH returns NIL or a vector. INFO-VECTOR-FDEFN accepts
72 ;; either. If fdefn isn't found, fall through to the legality test.
73 (awhen (info-vector-fdefn (info-gethash name *info-environment*))
74 (return-from find-fdefn it))
75 :simple
76 (progn
77 (awhen (symbol-info-vector key1)
78 (multiple-value-bind (data-idx descriptor-idx field-idx)
79 (info-find-aux-key/packed it key2)
80 (declare (type index descriptor-idx)
81 (type (integer 0 #.+infos-per-word+) field-idx))
82 ;; Secondary names must have at least one info, so if a descriptor
83 ;; exists, there's no need to extract the n-infos field.
84 (when data-idx
85 (when (eql (incf field-idx) +infos-per-word+)
86 (setq field-idx 0 descriptor-idx (1+ descriptor-idx)))
87 (when (eql (packed-info-field it descriptor-idx field-idx)
88 +fdefn-info-num+)
89 (return-from find-fdefn
90 (aref it (1- (the index data-idx))))))))
91 (when (eq key1 'setf) ; bypass the legality test
92 (return-from find-fdefn nil))))
93 (legal-fun-name-or-type-error name))
95 (declaim (ftype (sfunction (t) fdefn) find-or-create-fdefn))
96 (defun find-or-create-fdefn (name)
97 (or (find-fdefn name)
98 ;; We won't reach here if the name was not legal
99 (let ((fdefn (get-info-value-initializing :function :definition name
100 (make-fdefn name))))
101 (when (typep name '(cons (eql sb!pcl::slot-accessor)))
102 (sb!pcl::ensure-accessor name))
103 fdefn)))
105 ;;; Remove NAME's FTYPE information unless it was explicitly PROCLAIMED.
106 ;;; The NEW-FUNCTION argument is presently unused, but could be used
107 ;;; for checking compatibility of the NEW-FUNCTION against a proclamation.
108 ;;; (We could issue a warning and/or remove the type if incompatible.)
109 (defun maybe-clobber-ftype (name new-function)
110 (declare (ignore new-function))
111 (unless (eq :declared (info :function :where-from name))
112 (clear-info :function :type name)))
114 ;;; Return the fdefn-fun of NAME's fdefinition including any encapsulations.
115 ;;; LOOKUP-FN, defaulting to FIND-FDEFN, specifies how to lookup the fdefn.
116 ;;; As a special case it can be given as SYMBOL-FDEFN which is slightly quicker.
117 ;;; This is the core of the implementation of the standard FDEFINITION function,
118 ;;; but as we've defined FDEFINITION, that strips encapsulations.
119 (defmacro %coerce-name-to-fun (name &optional (lookup-fn 'find-fdefn)
120 strictly-functionp)
121 `(block nil
122 (let ((name ,name))
123 (tagbody retry
124 (let ((fdefn (,lookup-fn name)))
125 (when fdefn
126 (let ((f (fdefn-fun (truly-the fdefn fdefn))))
127 ;; If STRICTLY-FUNCTIONP is true, we make sure not to return an error
128 ;; trampoline. This extra check ensures that full calls such as
129 ;; (MAPCAR 'OR '()) signal an error that OR isn't a function.
130 ;; This accords with the non-requirement that macros store strictly
131 ;; a function in the symbol that names them. In many implementations,
132 ;; (FUNCTIONP (SYMBOL-FUNCTION 'OR)) => NIL. We want to pretend that.
133 (when f
134 (,@(if strictly-functionp
135 '(unless (macro/special-guard-fun-p f))
136 '(progn))
137 (return f)))))
138 (restart-case (error 'undefined-function :name name)
139 (continue ()
140 :report (lambda (stream)
141 (format stream "Retry using ~s." name)))
142 (use-value (value)
143 :report (lambda (stream)
144 (format stream "Use specified function"))
145 :interactive read-evaluated-form
146 (when (functionp value)
147 (return value))
148 (setf name (the ,(if (eq lookup-fn 'symbol-fdefn)
149 'symbol
151 value))))
152 (go retry))))))
154 ;; Return T if FUNCTION is the error-signaling trampoline
155 ;; for a macro or a special operator. Test for this by seeing
156 ;; whether FUNCTION is the same closure as for a known macro.
157 ;; For cold-init to work, this must pick any macro defined before
158 ;; this function is. A safe choice is a macro from this same file.
159 (declaim (inline macro/special-guard-fun-p))
160 (defun macro/special-guard-fun-p (function)
161 ;; When inlined, this is a few instructions shorter than CLOSUREP
162 ;; if we already know that FUNCTION is a function.
163 ;; It will signal a type error if not, which is the right thing to do anyway.
164 ;; (this isn't quite a true predicate)
165 (and (= (fun-subtype function) sb!vm:closure-header-widetag)
166 ;; Prior to cold-init fixing up the load-time-value, this compares
167 ;; %closure-fun to 0, which is ok - it returns NIL.
168 (eq (load-time-value (%closure-fun (symbol-function '%coerce-name-to-fun))
170 (%closure-fun function))))
172 ;; Coerce CALLABLE (a function-designator) to a FUNCTION.
173 ;; The compiler emits this when someone tries to FUNCALL something.
174 ;; Extended-function-designators are not accepted,
175 ;; This function declares EXPLICIT-CHECK, and we avoid calling
176 ;; SYMBOL-FUNCTION because that would do another check.
177 ;; It would be great if this could change its error message
178 ;; depending on the input to either:
179 ;; "foo is not a function designator" if not a CALLABLE
180 ;; "foo does not designate a currently defined function"
181 ;; if a symbol does not satisfy FBOUNDP.
182 (defun %coerce-callable-to-fun (callable)
183 (declare (explicit-check))
184 (etypecase callable
185 (function callable)
186 (symbol (%coerce-name-to-fun callable symbol-fdefn t))))
189 ;;;; definition encapsulation
191 (defstruct (encapsulation-info (:constructor make-encapsulation-info
192 (type definition))
193 (:copier nil))
194 ;; This is definition's encapsulation type. The encapsulated
195 ;; definition is in the previous ENCAPSULATION-INFO element or
196 ;; installed as the global definition of some function name.
197 type
198 ;; the previous, encapsulated definition. This used to be installed
199 ;; as a global definition for some function name, but it was
200 ;; replaced by an encapsulation of type TYPE.
201 (definition nil :type function))
203 ;;; Replace the definition of NAME with a function that calls FUNCTION
204 ;;; with the original function and its arguments.
205 ;;; TYPE is whatever you would like to associate with this
206 ;;; encapsulation for identification in case you need multiple
207 ;;; encapsulations of the same name.
208 (defun encapsulate (name type function)
209 (let* ((fdefn (find-fdefn name))
210 (underlying-fun (sb!c:safe-fdefn-fun fdefn)))
211 (when (typep underlying-fun 'generic-function)
212 (return-from encapsulate
213 (encapsulate-generic-function underlying-fun type function)))
214 ;; We must bind and close over INFO. Consider the case where we
215 ;; encapsulate (the second) an encapsulated (the first)
216 ;; definition, and later someone unencapsulates the encapsulated
217 ;; (first) definition. We don't want our encapsulation (second) to
218 ;; bind basic-definition to the encapsulated (first) definition
219 ;; when it no longer exists. When unencapsulating, we make sure to
220 ;; clobber the appropriate INFO structure to allow
221 ;; basic-definition to be bound to the next definition instead of
222 ;; an encapsulation that no longer exists.
223 (let ((info (make-encapsulation-info type underlying-fun)))
224 (setf (fdefn-fun fdefn)
225 (named-lambda encapsulation (&rest args)
226 (apply function (encapsulation-info-definition info)
227 args))))))
229 ;;; This is like FIND-IF, except that we do it on a compiled closure's
230 ;;; environment.
231 (defun find-if-in-closure (test closure)
232 (declare (closure closure))
233 (do-closure-values (value closure)
234 (when (funcall test value)
235 (return value))))
237 ;;; Find the encapsulation info that has been closed over.
238 (defun encapsulation-info (fun)
239 (when (closurep fun)
240 (find-if-in-closure #'encapsulation-info-p fun)))
242 ;;; When removing an encapsulation, we must remember that
243 ;;; encapsulating definitions close over a reference to the
244 ;;; ENCAPSULATION-INFO that describes the encapsulating definition.
245 ;;; When you find an info with the target type, the previous info in
246 ;;; the chain has the ensulating definition of that type. We take the
247 ;;; encapsulated definition from the info with the target type, and we
248 ;;; store it in the previous info structure whose encapsulating
249 ;;; definition it describes looks to this previous info structure for
250 ;;; a definition to bind (see ENCAPSULATE). When removing the first
251 ;;; info structure, we do something conceptually equal, but
252 ;;; mechanically it is different.
253 (defun unencapsulate (name type)
254 "Removes NAME's most recent encapsulation of the specified TYPE."
255 (let* ((fdefn (find-fdefn name))
256 (encap-info (encapsulation-info (fdefn-fun fdefn))))
257 (declare (type (or encapsulation-info null) encap-info))
258 (when (and fdefn (typep (fdefn-fun fdefn) 'generic-function))
259 (return-from unencapsulate
260 (unencapsulate-generic-function (fdefn-fun fdefn) type)))
261 (cond ((not encap-info)
262 ;; It disappeared on us, so don't worry about it.
264 ((eq (encapsulation-info-type encap-info) type)
265 ;; It's the first one, so change the fdefn object.
266 (setf (fdefn-fun fdefn)
267 (encapsulation-info-definition encap-info)))
269 ;; It must be an interior one, so find it.
270 (loop
271 (let ((next-info (encapsulation-info
272 (encapsulation-info-definition encap-info))))
273 (unless next-info
274 ;; Not there, so don't worry about it.
275 (return))
276 (when (eq (encapsulation-info-type next-info) type)
277 ;; This is it, so unlink us.
278 (setf (encapsulation-info-definition encap-info)
279 (encapsulation-info-definition next-info))
280 (return))
281 (setf encap-info next-info))))))
284 ;;; Does NAME have an encapsulation of the given TYPE?
285 (defun encapsulated-p (name type)
286 (let ((fdefn (find-fdefn name)))
287 (when (and fdefn (typep (fdefn-fun fdefn) 'generic-function))
288 (return-from encapsulated-p
289 (encapsulated-generic-function-p (fdefn-fun fdefn) type)))
290 (do ((encap-info (encapsulation-info (fdefn-fun fdefn))
291 (encapsulation-info
292 (encapsulation-info-definition encap-info))))
293 ((null encap-info) nil)
294 (declare (type (or encapsulation-info null) encap-info))
295 (when (eq (encapsulation-info-type encap-info) type)
296 (return t)))))
298 ;;;; FDEFINITION
300 ;;; KLUDGE: Er, it looks as though this means that
301 ;;; (FUNCALL (FDEFINITION 'FOO))
302 ;;; doesn't do the same thing as
303 ;;; (FUNCALL 'FOO),
304 ;;; and (SYMBOL-FUNCTION 'FOO) isn't in general the same thing
305 ;;; as (FDEFINITION 'FOO). That doesn't look like ANSI behavior to me.
306 ;;; Look e.g. at the ANSI definition of TRACE: "Whenever a traced
307 ;;; function is invoked, information about the call, ..". Try this:
308 ;;; (DEFUN FOO () (PRINT "foo"))
309 ;;; (TRACE FOO)
310 ;;; (FUNCALL 'FOO)
311 ;;; (FUNCALL (FDEFINITION 'FOO))
312 ;;; What to do? ANSI says TRACE "Might change the definitions of the
313 ;;; functions named by function-names." Might it be OK to just get
314 ;;; punt all this encapsulation stuff and go back to a simple but
315 ;;; correct implementation of TRACE? We'd lose the ability to redefine
316 ;;; a TRACEd function and keep the trace in place, but that seems
317 ;;; tolerable to me. (Is the wrapper stuff needed for anything else
318 ;;; besides TRACE?)
320 ;;; The only problem I can see with not having a wrapper: If tracing
321 ;;; EQ, EQL, EQUAL, or EQUALP causes its function address to change,
322 ;;; it will mess up the MAKE-HASH-TABLE logic which uses EQ tests
323 ;;; on those function values. But given the ANSI statement about
324 ;;; TRACE causing things to change, that doesn't seem too unreasonable;
325 ;;; and we might even be able to forbid tracing these functions.
326 ;;; -- WHN 2001-11-02
327 (defun fdefinition (name)
328 "Return name's global function definition taking care to respect any
329 encapsulations and to return the innermost encapsulated definition.
330 This is SETF'able."
331 (declare (explicit-check))
332 (let ((fun (%coerce-name-to-fun name)))
333 (loop
334 (let ((encap-info (encapsulation-info fun)))
335 (if encap-info
336 (setf fun (encapsulation-info-definition encap-info))
337 (return fun))))))
339 (defvar *setf-fdefinition-hook* nil
340 "A list of functions that (SETF FDEFINITION) invokes before storing the
341 new value. The functions take the function name and the new value.")
343 ;; Reject any "object of implementation-dependent nature" that
344 ;; so happens to be a function in SBCL, but which must not be
345 ;; bound to a function-name by way of (SETF FEDFINITION).
346 (defun err-if-unacceptable-function (object setter)
347 (declare (notinline macro/special-guard-fun-p)) ; not performance-critical
348 (when (macro/special-guard-fun-p object)
349 (error 'simple-reference-error
350 :references (list '(:ansi-cl :function fdefinition))
351 :format-control "~S is not acceptable to ~S."
352 :format-arguments (list object setter))))
354 (defun %set-fdefinition (name new-value)
355 "Set NAME's global function definition."
356 (declare (type function new-value) (optimize (safety 1)))
357 (declare (explicit-check))
358 (err-if-unacceptable-function new-value '(setf fdefinition))
359 (with-single-package-locked-error (:symbol name "setting fdefinition of ~A")
360 (maybe-clobber-ftype name new-value)
362 ;; Check for hash-table stuff. Woe onto him that mixes encapsulation
363 ;; with this.
364 (when (and (symbolp name) (fboundp name)
365 (boundp '*user-hash-table-tests*))
366 (let ((old (symbol-function name)))
367 (declare (special *user-hash-table-tests*))
368 (dolist (spec *user-hash-table-tests*)
369 (cond ((eq old (second spec))
370 ;; test-function
371 (setf (second spec) new-value))
372 ((eq old (third spec))
373 ;; hash-function
374 (setf (third spec) new-value))))))
376 ;; FIXME: This is a good hook to have, but we should probably
377 ;; reserve it for users.
378 (let ((fdefn (find-or-create-fdefn name)))
379 ;; *SETF-FDEFINITION-HOOK* won't be bound when initially running
380 ;; top level forms in the kernel core startup.
381 (when (boundp '*setf-fdefinition-hook*)
382 (dolist (f *setf-fdefinition-hook*)
383 (declare (type function f))
384 (funcall f name new-value)))
386 (let ((encap-info (encapsulation-info (fdefn-fun fdefn))))
387 (cond (encap-info
388 (loop
389 (let ((more-info
390 (encapsulation-info
391 (encapsulation-info-definition encap-info))))
392 (if more-info
393 (setf encap-info more-info)
394 (return
395 (setf (encapsulation-info-definition encap-info)
396 new-value))))))
398 (setf (fdefn-fun fdefn) new-value)))))))
400 ;;;; FBOUNDP and FMAKUNBOUND
402 (defun fboundp (name)
403 "Return true if name has a global function definition."
404 (declare (explicit-check))
405 (let ((fdefn (find-fdefn name)))
406 (and fdefn (fdefn-fun fdefn) t)))
408 ;; Byte index 2 of the fdefn's header is the statically-linked flag
409 #!+immobile-code
410 (defmacro sb!vm::fdefn-has-static-callers (fdefn)
411 `(sap-ref-8 (int-sap (get-lisp-obj-address ,fdefn))
412 (- 2 sb!vm::other-pointer-lowtag)))
414 (defun fmakunbound (name)
415 "Make NAME have no global function definition."
416 (declare (explicit-check))
417 (with-single-package-locked-error
418 (:symbol name "removing the function or macro definition of ~A")
419 (let ((fdefn (find-fdefn name)))
420 (when fdefn
421 #!+immobile-code
422 (unless (eql (sb!vm::fdefn-has-static-callers fdefn) 0)
423 (sb!vm::remove-static-links fdefn))
424 (fdefn-makunbound fdefn)))
425 (undefine-fun-name name)
426 name))