Derive the type of COPY-LIST.
[sbcl.git] / src / code / ntrace.lisp
blobdd0cddca57a60e23a6a47cbcf3375bd0ef43bea0
1 ;;;; a tracing facility
3 ;;;; This software is part of the SBCL system. See the README file for
4 ;;;; more information.
5 ;;;;
6 ;;;; This software is derived from the CMU CL system, which was
7 ;;;; written at Carnegie Mellon University and released into the
8 ;;;; public domain. The software is in the public domain and is
9 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
10 ;;;; files for more information.
12 (in-package "SB-DEBUG")
14 ;;; FIXME: Why, oh why, doesn't the SB-DEBUG package use the SB-DI
15 ;;; package? That would let us get rid of a whole lot of stupid
16 ;;; prefixes..
18 ;;;; utilities
20 ;;; Given X -- a function object or an s-expression naming a global function,
21 ;;; local function, method, macro or compiler-macro -- return the following
22 ;;; values:
23 ;;; * a function object suitable for introspection via
24 ;;; SB-DI:FUN-DEBUG-FUN. For local functions, their parent function is
25 ;;; returned. For methods, their generic function is returned, unless
26 ;;; IF-METHOD is :FAST-METHOD, in which case their respective
27 ;;; SB-PCL::FAST-METHOD function is returned.
28 ;;; * The function's BLOCK name, useful for looking up local functions.
29 ;;; * A keyword symbol describing what X denotes: :ANONYMOUS-FUNCTION,
30 ;;; :FUNCTION, :LOCAL-FUNCTION, :METHOD, :MACRO-FUNCTION.
31 ;;; * [For local functions only] A local name suitable for SB-DI:FUN-DEBUG-FUN
32 ;;; lookup.
33 (defun %trace-fdefinition (x &key (if-method :gf) definition)
34 (typecase x
35 (function
36 (values x nil :anonymous-function))
37 ((cons (eql compiler-macro) (cons t null))
38 (let ((fun (or definition (compiler-macro-function (second x)))))
39 (if fun
40 (values fun (second x) :compiler-macro)
41 (warn "~S is undefined, not tracing." x))))
42 ((cons (eql method)) ; (METHOD name qualifiers (specializers*))
43 (assert (null definition))
44 (multiple-value-bind (gf block-name)
45 (%trace-fdefinition (second x))
46 (when gf
47 (if (find-method gf (butlast (cddr x)) (car (last x)) nil)
48 (ecase if-method
49 (:fast-method
50 (%trace-fdefinition `(sb-pcl::fast-method ,@(rest x))))
51 (:gf
52 (values gf block-name :method)))
53 (warn "~S not found, not tracing." x)))))
54 ((cons (member flet labels)) ; ({FLET,LABELS} name :IN outer-function)
55 (destructuring-bind (flet/labels name &key in) x
56 (multiple-value-bind (fun block-name)
57 (%trace-fdefinition in :if-method :fast-method :definition definition)
58 (when fun
59 (let ((local-name `(,flet/labels ,name :in ,block-name)))
60 (if (sb-di:fun-debug-fun fun :local-name local-name)
61 (values fun nil :local-function local-name)
62 (warn "~S not found, not tracing." x)))))))
63 ((and symbol (satisfies special-operator-p))
64 (warn "~S is a special operator, not tracing." x))
65 ((and symbol (satisfies macro-function))
66 (values (or definition (macro-function x)) x :macro-function))
68 (multiple-value-bind (valid block-name)
69 (valid-function-name-p x)
70 (cond ((not valid)
71 (warn "~S is not a valid function name, not tracing." x))
72 ((fboundp x)
73 (values (or definition (fdefinition x)) block-name :function))
75 (warn "~/sb-ext:print-symbol-with-prefix/ is ~
76 undefined, not tracing." x)))))))
78 (defun trace-fdefinition (x &optional definition)
79 (multiple-value-bind (fun block-name kind local-name)
80 (%trace-fdefinition x :definition definition)
81 (declare (ignore block-name))
82 (values fun kind local-name)))
84 (defun retrace-local-funs (fname &optional new-value)
85 (dolist (local (gethash fname *traced-locals*))
86 (let ((trace-info (gethash local *traced-funs*)))
87 (untrace-1 local)
88 (trace-1 local trace-info new-value))))
90 ;;; When a function name is redefined, and we were tracing that name,
91 ;;; then untrace the old definition and trace the new one.
92 (defun maybe-retrace (name new-value)
93 (let ((info (gethash name *traced-funs*)))
94 (when info
95 (untrace-1 name)
96 (trace-1 name info new-value))
97 (retrace-local-funs name new-value)))
99 (defun maybe-retrace-function (name new-value)
100 (when (fboundp name)
101 (maybe-retrace name new-value)))
103 (push #'maybe-retrace-function *setf-fdefinition-hook*)
104 (push #'maybe-retrace-function *setf-macro-function-hook*)
106 (defun maybe-retrace-compiler-macro (name new-value)
107 (when (compiler-macro-function name)
108 (maybe-retrace `(compiler-macro ,name) new-value)))
110 (push #'maybe-retrace-compiler-macro *setf-compiler-macro-function-hook*)
112 ;;; Annotate a FORM to evaluate with pre-converted functions. FORM is
113 ;;; really a cons (EXP . FUNCTION). LOC is the code location to use
114 ;;; for the lexical environment. If LOC is NIL, evaluate in the null
115 ;;; environment. If FORM is NIL, just return NIL.
116 (defun coerce-form (form loc)
117 (when form
118 (let ((exp (car form)))
119 (if (sb-di:code-location-p loc)
120 (let ((fun (sb-di:preprocess-for-eval exp loc)))
121 (declare (type function fun))
122 (cons exp
123 (lambda (frame &rest args)
124 (declare (ignore args))
125 (let ((*current-frame* frame))
126 (funcall fun frame)))))
127 (let* ((body `(locally (declare (disable-package-locks sb-debug:arg))
128 (flet ((sb-debug:arg (n)
129 (elt args n)))
130 (declare (ignorable #'sb-debug:arg)
131 (enable-package-locks sb-debug:arg))
132 ,exp)))
133 (fun (coerce `(lambda (&rest args) (declare (ignorable args))
134 ,body) 'function)))
135 (cons exp
136 (lambda (frame &rest args)
137 (declare (ignore frame))
138 (let ((*current-frame* nil))
139 (apply fun args)))))))))
141 (defun coerce-form-list (forms loc)
142 (mapcar (lambda (x) (coerce-form x loc)) forms))
144 ;;; Print indentation according to the number of trace entries.
145 ;;; Entries whose condition was false don't count.
146 (defun print-trace-indentation ()
147 (let* ((depth (count-if #'cdr *traced-entries*))
148 (step *trace-indentation-step*)
149 (max *max-trace-indentation*)
150 (indent (+ (mod (* depth step) (- max step)) step)))
151 (format t "~V,0@T~W: " indent depth)))
153 ;;; Return true if any of the NAMES appears on the stack below FRAME.
154 (defun trace-wherein-p (encapsulated frame names)
155 ;; When tracing without encapsulation (i.e. when using breakpoints),
156 ;; FRAME points to the function being traced, so skip it.
157 (let ((initial-frame (if encapsulated frame (sb-di:frame-down frame))))
158 (do ((frame initial-frame (sb-di:frame-down frame)))
159 ((not frame) nil)
160 (when (member (sb-di:debug-fun-name (sb-di:frame-debug-fun frame))
161 names
162 :test #'equal)
163 (return t)))))
165 ;;; Handle PRINT and PRINT-AFTER options.
166 (defun trace-print (frame forms &rest args)
167 (dolist (ele forms)
168 (fresh-line)
169 (print-trace-indentation)
170 (format t "~@<~S ~_= ~:[; No values~;~:*~{~S~^, ~}~]~:>"
171 (car ele)
172 (multiple-value-list (apply (cdr ele) frame args)))
173 (terpri)))
175 ;;; Handle PRINT and PRINT-AFTER options when :REPORT style is NIL.
176 (defun trace-print-unadorned (frame forms &rest args)
177 (dolist (ele forms)
178 (let ((values (multiple-value-list (apply (cdr ele) frame args))))
179 (when values
180 (format t "~&~{~A~^, ~}~%" values)))))
182 ;;; Test a BREAK option, and if true, break.
183 (defun trace-maybe-break (info break where frame &rest args)
184 (when (and break (apply (cdr break) frame args))
185 (sb-di:flush-frames-above frame)
186 (let ((*stack-top-hint* frame))
187 (break "breaking ~A traced call to ~S:"
188 where
189 (trace-info-what info)))))
191 ;;; Discard any invalid cookies on our simulated stack. Encapsulated
192 ;;; entries are always valid, since we bind *TRACED-ENTRIES* in the
193 ;;; encapsulation.
194 (defun discard-invalid-entries (frame)
195 (loop
196 (when (or (null *traced-entries*)
197 (let ((cookie (caar *traced-entries*)))
198 (or (not cookie)
199 (sb-di:fun-end-cookie-valid-p frame cookie))))
200 (return))
201 (pop *traced-entries*)))
203 ;;;; hook functions
205 ;;; Return a closure that can be used for a function start breakpoint
206 ;;; hook function and a closure that can be used as the FUN-END-COOKIE
207 ;;; function. The first communicates the sense of the
208 ;;; TRACE-INFO-CONDITION to the second via a closure variable.
209 (defun trace-start-breakpoint-fun (info)
210 (let (conditionp)
211 (values
212 ;; HOOK-ARGS holds the function arguments when tracing via
213 ;; encapsulation and but is NIL when tracing via breakpoints.
214 (lambda (frame bpt &rest hook-args)
215 (declare (ignore bpt))
216 (discard-invalid-entries frame)
217 (let ((condition (trace-info-condition info))
218 (wherein (trace-info-wherein info)))
219 (setq conditionp
220 (and (not *in-trace*)
221 (or (not condition)
222 (apply (cdr condition) frame hook-args))
223 (or (not wherein)
224 (trace-wherein-p (trace-info-encapsulated info) frame wherein)))))
225 (when conditionp
226 (with-standard-io-syntax
227 (let ((*print-readably* nil)
228 (*current-level-in-print* 0)
229 (*standard-output* (make-string-output-stream))
230 (*print-pretty* t)
231 (*in-trace* t))
232 (case (trace-info-report info)
233 (trace
234 (fresh-line)
235 (print-trace-indentation)
236 (if (trace-info-encapsulated info)
237 (prin1 `(,(trace-info-what info)
238 ,@(mapcar #'ensure-printable-object hook-args)))
239 (print-frame-call frame *standard-output*))
240 (terpri)
241 (apply #'trace-print frame (trace-info-print info) hook-args))
242 ((nil)
243 (apply #'trace-print-unadorned frame (trace-info-print info) hook-args))
245 (funcall (trace-info-report info)
246 (count-if #'cdr *traced-entries*)
247 (trace-info-what info) :enter frame
248 (if (trace-info-encapsulated info)
249 hook-args
250 (nth-value 1 (frame-call frame))))
251 (apply #'trace-print-unadorned frame (trace-info-print info) hook-args)))
252 (write-sequence (get-output-stream-string *standard-output*)
253 *trace-output*)
254 (finish-output *trace-output*))
255 (apply #'trace-maybe-break info (trace-info-break info) "before"
256 frame hook-args))))
257 (lambda (frame cookie)
258 (declare (ignore frame))
259 (push (cons cookie conditionp) *traced-entries*)))))
261 ;;; This prints a representation of the return values delivered.
262 ;;; First, this checks to see that cookie is at the top of
263 ;;; *TRACED-ENTRIES*; if it is not, then we need to adjust this list
264 ;;; to determine the correct indentation for output. We then check to
265 ;;; see whether the function is still traced and that the condition
266 ;;; succeeded before printing anything.
267 (declaim (ftype (function (trace-info) function) trace-end-breakpoint-fun))
268 (defun trace-end-breakpoint-fun (info)
269 (lambda (frame bpt-or-nle values cookie)
270 (unless (eq cookie (caar *traced-entries*))
271 (setf *traced-entries*
272 (member cookie *traced-entries* :key #'car)))
274 (let ((entry (pop *traced-entries*))
275 (non-local-exit (eq bpt-or-nle :nle)))
276 (when (and (not (trace-info-untraced info))
277 (or (cdr entry)
278 (let ((cond (trace-info-condition-after info)))
279 (and cond (apply #'funcall (cdr cond) frame values)))))
280 (let ((*current-level-in-print* 0)
281 (*standard-output* (make-string-output-stream))
282 (*in-trace* t))
283 (case (trace-info-report info)
284 (trace
285 (fresh-line)
286 (let ((*print-pretty* t))
287 (pprint-logical-block (*standard-output* nil)
288 (print-trace-indentation)
289 (pprint-indent :current 2)
290 (cond (non-local-exit
291 (format t "~S exited non-locally" (trace-info-what info)))
293 (format t "~S returned" (trace-info-what info))
294 (dolist (v values)
295 (write-char #\space)
296 (pprint-newline :linear)
297 (prin1 (ensure-printable-object v))))))
298 (terpri))
299 (unless non-local-exit
300 (apply #'trace-print frame (trace-info-print-after info) values)))
301 ((nil)
302 (unless non-local-exit
303 (apply #'trace-print-unadorned frame (trace-info-print-after info) values)))
305 (funcall (trace-info-report info)
306 (count-if #'cdr *traced-entries*)
307 (trace-info-what info)
308 (if non-local-exit :non-local-exit :exit)
309 frame
310 values)
311 (apply #'trace-print-unadorned frame (trace-info-print-after info) values)))
312 (write-sequence (get-output-stream-string *standard-output*)
313 *trace-output*)
314 (finish-output *trace-output*))
315 (apply #'trace-maybe-break info (trace-info-break-after info) "after"
316 frame values)))))
318 ;;; This function is called by the trace encapsulation. It calls the
319 ;;; breakpoint hook functions with NIL for the breakpoint and cookie,
320 ;;; which we have cleverly contrived to work for our hook functions.
321 (defun trace-call (info function &rest args)
322 (multiple-value-bind (start cookie) (trace-start-breakpoint-fun info)
323 (declare (type function start cookie))
324 (let ((frame (sb-di:frame-down (sb-di:top-frame))))
325 (apply #'funcall start frame nil args)
326 (let ((*traced-entries* *traced-entries*))
327 (funcall cookie frame nil)
328 (let* ((non-local-exit '#:nle)
329 (vals non-local-exit))
330 (unwind-protect
331 (setq vals (multiple-value-list (apply function args)))
332 (funcall (trace-end-breakpoint-fun info)
333 frame
334 (if (eq vals non-local-exit) :nle nil)
335 (if (eq vals non-local-exit) nil vals)
336 nil))
337 (values-list vals))))))
339 ;;; This function is like TRACE-CALL above, but munges the method
340 ;;; calling conventions into something more like what the user might
341 ;;; expect to see -- so not (<args> <next methods>) or (<permutation
342 ;;; vector> <next-emf> <arg> ...), but the method's actual arglist.
343 (defun trace-method-call (info function fmf-p &rest args)
344 (let ((transform (if fmf-p (lambda (x) (nthcdr 2 x)) #'car)))
345 (multiple-value-bind (start cookie) (trace-start-breakpoint-fun info)
346 (declare (type function start cookie))
347 (let ((frame (sb-di:frame-down (sb-di:top-frame))))
348 (apply #'funcall start frame nil (funcall transform args))
349 (let ((*traced-entries* *traced-entries*))
350 (funcall cookie frame nil)
351 (let* ((non-local-exit '#:nle)
352 (vals non-local-exit))
353 (unwind-protect
354 (setq vals (multiple-value-list (apply function args)))
355 (funcall (trace-end-breakpoint-fun info)
356 frame
357 (if (eq vals non-local-exit) :nle nil)
358 (if (eq vals non-local-exit) nil vals)
359 nil))
360 (values-list vals)))))))
362 ;;; Trace one function according to the specified options. We copy the
363 ;;; trace info (it was a quoted constant), fill in the functions, and
364 ;;; then install the breakpoints or encapsulation.
366 ;;; If non-null, DEFINITION is the new definition of a function that
367 ;;; we are automatically retracing.
368 (defun trace-1 (function-or-name info &optional definition)
369 (multiple-value-bind (fun kind local-name)
370 (trace-fdefinition function-or-name definition)
371 (when fun
372 (when (closurep fun)
373 (setq fun (%closure-fun fun))
374 (when (eq (trace-info-encapsulated info) :default)
375 (warn "tracing shared code for ~S:~% ~S" function-or-name fun)))
376 (when (gethash function-or-name *traced-funs*)
377 (warn "~S is already TRACE'd, untracing it first." function-or-name)
378 (untrace-1 function-or-name))
379 (let* ((debug-fun (sb-di:fun-debug-fun fun :local-name local-name))
380 (encapsulated
381 (ecase kind
382 ((:function :method)
383 (if (eq (trace-info-encapsulated info) :default)
384 (funcallable-instance-p fun)
385 (trace-info-encapsulated info)))
386 ((:anonymous-function :compiler-macro :macro-function :local-function)
387 nil)))
388 (loc (if encapsulated
389 :encapsulated
390 (sb-di:debug-fun-start-location debug-fun)))
391 (info (make-trace-info
392 :what function-or-name
393 :encapsulated encapsulated
394 :wherein (trace-info-wherein info)
395 :methods (trace-info-methods info)
396 :condition (coerce-form (trace-info-condition info) loc)
397 :break (coerce-form (trace-info-break info) loc)
398 :report (trace-info-report info)
399 :print (coerce-form-list (trace-info-print info) loc)
400 :break-after (coerce-form (trace-info-break-after info) nil)
401 :condition-after
402 (coerce-form (trace-info-condition-after info) nil)
403 :print-after
404 (coerce-form-list (trace-info-print-after info) nil))))
406 (dolist (wherein (trace-info-wherein info))
407 (unless (or (stringp wherein)
408 (fboundp wherein))
409 (warn ":WHEREIN name ~S is not a defined global function."
410 wherein)))
412 (cond
413 (encapsulated
414 (if (eq kind :method)
415 (reinitialize-instance fun)
416 (encapsulate function-or-name 'trace
417 (lambda (function &rest args)
418 (apply #'trace-call info function args)))))
420 (multiple-value-bind (start-fun cookie-fun)
421 (trace-start-breakpoint-fun info)
422 (let ((start (sb-di:make-breakpoint start-fun debug-fun
423 :kind :fun-start))
424 (end (sb-di:make-breakpoint
425 (trace-end-breakpoint-fun info)
426 debug-fun :kind :fun-end
427 :fun-end-cookie cookie-fun)))
428 (setf (trace-info-start-breakpoint info) start)
429 (setf (trace-info-end-breakpoint info) end)
430 ;; The next two forms must be in the order in which they
431 ;; appear, since the start breakpoint must run before the
432 ;; fun-end breakpoint's start helper (which calls the
433 ;; cookie function.) One reason is that cookie function
434 ;; requires that the CONDITIONP shared closure variable be
435 ;; initialized.
436 (sb-di:activate-breakpoint start)
437 (sb-di:activate-breakpoint end)))))
439 (when (eq kind :local-function)
440 (push function-or-name
441 (gethash (fourth function-or-name) *traced-locals*)))
442 (setf (gethash function-or-name *traced-funs*) info))
444 (when (and (typep fun 'generic-function)
445 (trace-info-methods info)
446 ;; we are going to trace the method functions directly.
447 (not (trace-info-encapsulated info)))
448 (dolist (method (sb-mop:generic-function-methods fun))
449 (let ((mf (sb-mop:method-function method)))
450 ;; NOTE: this direct style of tracing methods -- tracing the
451 ;; pcl-internal method functions -- is only one possible
452 ;; alternative. It fails (a) when encapsulation is
453 ;; requested, because the function objects themselves are
454 ;; stored in the method object; (b) when the method in
455 ;; question is particularly simple, when the method
456 ;; functionality is in the dfun.
457 (trace-1 mf info)
458 (when (typep mf 'sb-pcl::%method-function)
459 (trace-1 (sb-pcl::%method-function-fast-function mf) info)))))
461 function-or-name)))
463 ;;;; the TRACE macro
465 ;;; Parse leading trace options off of SPECS, modifying INFO
466 ;;; accordingly. The remaining portion of the list is returned when we
467 ;;; encounter a plausible function name.
468 (defun parse-trace-options (specs info)
469 (let ((current specs))
470 (loop
471 (when (endp current) (return))
472 (let ((option (first current))
473 (value (cons (second current) nil)))
474 (case option
475 (:report
476 (unless (typep (car value) 'trace-report-type)
477 (error "~S is not a valid ~A ~S type."
478 (car value) 'trace :report))
479 (setf (trace-info-report info) (car value)))
480 (:condition (setf (trace-info-condition info) value))
481 (:condition-after
482 (setf (trace-info-condition info) (cons nil nil))
483 (setf (trace-info-condition-after info) value))
484 (:condition-all
485 (setf (trace-info-condition info) value)
486 (setf (trace-info-condition-after info) value))
487 (:wherein
488 (setf (trace-info-wherein info)
489 (if (listp (car value)) (car value) value)))
490 (:encapsulate
491 (setf (trace-info-encapsulated info) (car value)))
492 (:methods
493 (setf (trace-info-methods info) (car value)))
494 (:break (setf (trace-info-break info) value))
495 (:break-after (setf (trace-info-break-after info) value))
496 (:break-all
497 (setf (trace-info-break info) value)
498 (setf (trace-info-break-after info) value))
499 (:print
500 (setf (trace-info-print info)
501 (append (trace-info-print info) (list value))))
502 (:print-after
503 (setf (trace-info-print-after info)
504 (append (trace-info-print-after info) (list value))))
505 (:print-all
506 (setf (trace-info-print info)
507 (append (trace-info-print info) (list value)))
508 (setf (trace-info-print-after info)
509 (append (trace-info-print-after info) (list value))))
510 (t (return)))
511 (pop current)
512 (unless current
513 (error "missing argument to ~S TRACE option" option))
514 (pop current)))
515 current))
517 ;;; Compute the expansion of TRACE in the non-trivial case (arguments
518 ;;; specified.)
519 (defun expand-trace (specs)
520 (collect ((binds)
521 (forms))
522 (let* ((global-options (make-trace-info))
523 (current (parse-trace-options specs global-options)))
524 (loop
525 (when (endp current) (return))
526 (let* ((name (pop current))
527 (fn (when (eq name :function)
528 (pop current)))
529 (options (copy-trace-info global-options)))
530 ;; parse options for the current spec.
531 (setq current (parse-trace-options current options))
532 (cond
533 ((eq name :function)
534 (let ((temp (gensym)))
535 (binds `(,temp ,fn))
536 (forms `(trace-1 ,temp ',options))))
537 ((and (keywordp name)
538 (not (or (fboundp name) (macro-function name))))
539 (error "unknown TRACE option: ~S" name))
540 ((stringp name)
541 (let ((package (find-undeleted-package-or-lose name)))
542 (do-all-symbols (symbol (find-package name))
543 (when (eql package (symbol-package symbol))
544 (when (and (fboundp symbol)
545 (not (macro-function symbol))
546 (not (special-operator-p symbol)))
547 (forms `(trace-1 ',symbol ',options)))
548 (let ((setf-name `(setf ,symbol)))
549 (when (fboundp setf-name)
550 (forms `(trace-1 ',setf-name ',options))))))))
551 ;; special-case METHOD (without encapsulation): it itself
552 ;; is not a general function name symbol, but it (at least
553 ;; here) designates one of a pair of such.
554 ((and (consp name)
555 (eq (car name) 'method)
556 (not (trace-info-encapsulated options)))
557 (when (fboundp (list* 'sb-pcl::slow-method (cdr name)))
558 (forms `(trace-1 ',(list* 'sb-pcl::slow-method (cdr name))
559 ',options)))
560 (when (fboundp (list* 'sb-pcl::fast-method (cdr name)))
561 (forms `(trace-1 ',(list* 'sb-pcl::fast-method (cdr name))
562 ',options))))
564 (forms `(trace-1 ',name ',options)))))))
565 `(let ,(binds)
566 (remove nil (list ,@(forms))))))
568 (defun %list-traced-funs ()
569 (loop for x being each hash-value in *traced-funs*
570 collect (trace-info-what x)))
572 (defmacro trace (&rest specs)
573 "TRACE {Option Global-Value}* {Name {Option Value}*}*
575 TRACE is a debugging tool that provides information when specified
576 functions are called. In its simplest form:
578 (TRACE NAME-1 NAME-2 ...)
580 The NAMEs are not evaluated. Each may be one of the following:
581 * SYMBOL, denoting a function or macro.
582 * FNAME, a valid function name, denoting a function.
583 * (METHOD FNAME QUALIFIERS* (SPECIALIZERS*)) denoting a method.
584 * (COMPILER-MACRO SYMBOL) denoting a compiler macro.
585 * (LABELS FNAME :IN OUTER-NAME) or (FLET FNAME :IN OUTER-NAME)
586 denoting a local function where OUTER-NAME may be any of the
587 previous names for functions, macros, methods or compiler macros.
588 Tracing local functions may require DEBUG policy 3 to inhibit
589 inlining.
590 * STRING denoting all functions fbound to symbols whose home package
591 is the package with the given name.
593 Options allow modification of the default behavior. Each option is a
594 pair of an option keyword and a value form. Global options are
595 specified before the first name, and affect all functions traced by a
596 given use of TRACE. Options may also be interspersed with function
597 names, in which case they act as local options, only affecting tracing
598 of the immediately preceding function name. Local options override
599 global options.
601 By default, TRACE causes a printout on *TRACE-OUTPUT* each time that
602 one of the named functions is entered or returns. (This is the basic,
603 ANSI Common Lisp behavior of TRACE.)
605 The following options are defined:
607 :REPORT Report-Type
608 If Report-Type is TRACE (the default) then information is
609 reported by printing immediately. If Report-Type is NIL, then
610 the only effect of the trace is to execute other
611 options (e.g. PRINT or BREAK). Otherwise, Report-Type is
612 treated as a function designator and, for each trace event,
613 funcalled with 5 arguments: trace depth (a non-negative
614 integer), a function name or a function object, a
615 keyword (:ENTER, :EXIT or :NON-LOCAL-EXIT), a stack frame, and
616 a list of values (arguments or return values).
618 :CONDITION Form
619 :CONDITION-AFTER Form
620 :CONDITION-ALL Form
621 If :CONDITION is specified, then TRACE does nothing unless Form
622 evaluates to true at the time of the call. :CONDITION-AFTER is
623 similar, but suppresses the initial printout, and is tested when the
624 function returns. :CONDITION-ALL tries both before and after.
626 :BREAK Form
627 :BREAK-AFTER Form
628 :BREAK-ALL Form
629 If specified, and Form evaluates to true, then the debugger is invoked
630 at the start of the function, at the end of the function, or both,
631 according to the respective option.
633 :PRINT Form
634 :PRINT-AFTER Form
635 :PRINT-ALL Form
636 In addition to the usual printout, the result of evaluating Form is
637 printed at the start of the function, at the end of the function, or
638 both, according to the respective option. Multiple print options cause
639 multiple values to be printed.
641 :WHEREIN Names
642 If specified, Names is a function name or list of names. TRACE does
643 nothing unless a call to one of those functions encloses the call to
644 this function (i.e. it would appear in a backtrace.) Anonymous
645 functions have string names like \"DEFUN FOO\".
647 :ENCAPSULATE {:DEFAULT | T | NIL}
648 If T, the default, tracing is done via encapsulation (redefining the
649 function name) rather than by modifying the function. :DEFAULT is
650 not the default, but means to use encapsulation for interpreted
651 functions and funcallable instances, breakpoints otherwise. When
652 encapsulation is used, forms are *not* evaluated in the function's
653 lexical environment, but SB-DEBUG:ARG can still be used.
655 :METHODS {T | NIL}
656 If T, any function argument naming a generic function will have its
657 methods traced in addition to the generic function itself.
659 :FUNCTION Function-Form
660 This is a not really an option, but rather another way of specifying
661 what function to trace. The Function-Form is evaluated immediately,
662 and the resulting function is traced.
664 :CONDITION, :BREAK and :PRINT forms are evaluated in a context which
665 mocks up the lexical environment of the called function, so that
666 SB-DEBUG:VAR and SB-DEBUG:ARG can be used.
667 The -AFTER and -ALL forms can use also use SB-DEBUG:ARG. In forms
668 which are evaluated after the function call, (SB-DEBUG:ARG N) returns
669 the N-th value returned by the function."
670 (if specs
671 (expand-trace specs)
672 '(%list-traced-funs)))
674 ;;;; untracing
676 ;;; Untrace one function.
677 (defun untrace-1 (function-or-name)
678 (multiple-value-bind (fun kind)
679 (trace-fdefinition function-or-name)
680 (when fun
681 (let ((info (gethash function-or-name *traced-funs*)))
682 (cond ((and fun (not info))
683 (warn "Function is not TRACEd: ~S" function-or-name))
685 (cond
686 ((trace-info-encapsulated info)
687 (if (eq kind :method)
688 (reinitialize-instance fun)
689 (unencapsulate (trace-info-what info) 'trace)))
691 (sb-di:delete-breakpoint (trace-info-start-breakpoint info))
692 (sb-di:delete-breakpoint (trace-info-end-breakpoint info))))
693 (setf (trace-info-untraced info) t)
694 (when (eq kind :local-function)
695 (let ((table *traced-locals*)
696 (outer (fourth function-or-name)))
697 (with-system-mutex ((hash-table-lock table))
698 (let* ((locals (gethash outer table))
699 (remaining (remove function-or-name locals :test #'equal)))
700 (if remaining
701 (setf (gethash outer table) remaining)
702 (remhash outer table))))))))))
703 (remhash function-or-name *traced-funs*)))
705 ;;; Untrace all traced functions.
706 (defun untrace-all ()
707 (dolist (fun (%list-traced-funs))
708 (untrace-1 fun))
711 (defun untrace-package (name)
712 (let ((package (find-package name)))
713 (when package
714 (dolist (fun (%list-traced-funs))
715 (cond ((and (symbolp fun) (eq package (symbol-package fun)))
716 (untrace-1 fun))
717 ((and (consp fun) (eq 'setf (car fun))
718 (symbolp (second fun))
719 (eq package (symbol-package (second fun))))
720 (untrace-1 fun)))))))
722 (defmacro untrace (&rest specs)
723 "Remove tracing from the specified functions. Untraces all
724 functions when called with no arguments."
725 (if specs
726 `(progn
727 ,@(loop for name = (car specs)
728 while specs
729 do (pop specs)
730 collect (cond ((eq name :function)
731 `(untrace-1 ,(pop specs)))
732 ((stringp name)
733 `(untrace-package ,name))
735 `(untrace-1 ',name))))
737 '(untrace-all)))
739 ;;;; Experimental implementation of encapsulation, specifically for TRACE,
740 ;;;; which preserves identity of closures and simple-funs.
742 ;;; Code which is traced has simple-funs whose entry points do not point
743 ;;; to themselves. The garbage collector needs to visit each simple-fun
744 ;;; in the traced object when scavenging. Normally it does not do that,
745 ;;; as relocation of the etry point is performed by the transport method,
746 ;;; not the scavenge method.
747 (defconstant code-is-traced 1)
749 (defun set-tracing-bit (code bit)
750 (declare (ignorable code bit))
751 ;; there are no bits to spare in a 32-bit header word,
752 ;; and with darwin-jit it's not worth the extra complexity
753 #+(and 64-bit (not darwin-jit))
754 (with-pinned-objects (code)
755 (let ((sap (int-sap (get-lisp-obj-address code))))
756 ;; NB: This is not threadsafe on machines that don't promise that
757 ;; stores to single bytes are atomic.
758 (setf (sap-ref-8 sap #+little-endian (- 2 sb-vm:other-pointer-lowtag)
759 #+big-endian (- 5 sb-vm:other-pointer-lowtag))
760 bit)
761 ;; touch the card mark - WHY???
762 (setf (code-header-ref code 1) (code-header-ref code 1)))))
764 ;;; FIXME: Symbol is lost by accident
765 (eval-when (:compile-toplevel :load-toplevel)
766 (export 'sb-int::encapsulate-funobj 'sb-int))
768 ;;; Suppose you want to trace function #'FOO no matter how a caller
769 ;;; references it (maybe capturing #'FOO in a variable before asking
770 ;;; to trace FOO). We can do that without resorting to breakpoints,
771 ;;; by replacing the simple-fun entry point in the header of the code
772 ;;; that contains FOO such that it points to a different simple-fun
773 ;;; outside of itself. That other simple-fun calls the tracing routine
774 ;;; and then the real FOO. An entry point can't be replaced with a
775 ;;; closure, because CLOSURE and SIMPLE-FUN are not fungible.
777 ;;; +-------------------------+ +--------------------+
778 ;;; | codeblob foo | | codeblob "TRACER" |
779 ;;; | ... | | |
780 ;;; | ... boxed data ... | | boxed word: #'foo | -> the "real" FOO
781 ;;; | ... | | |
782 ;;; | ... unboxed data ... | | |
783 ;;; | ... | +--------------------+
784 ;;; | simple-fun-header #'foo | --> | call trace helper |
785 ;;; | redirected entry point | --/ +--------------------+
786 ;;; | instructions of #'FOO |
787 ;;; | ... |
788 ;;; +-------------------------+
790 (defun compile-funobj-encapsulation (wrapper info actual-fun)
791 #+(or x86 x86-64)
792 (let ((code
793 ;; Don't actually "compile" - just emulate the result of compiling.
794 ;; Cloning a precompiled template object consumes only 272 bytes
795 ;; versus about 128KB to invoke the compiler.
796 (sb-c::copy-code-object
797 (load-time-value
798 (let ((c (fun-code-header
799 ;; Immobile code might use relative fixups which won't work
800 ;; when the code gets copied.
801 (let ((sb-c:*compile-to-memory-space* :dynamic))
802 (compile nil
803 `(lambda (&rest args)
804 ;; The code constants will be overwritten in the copy.
805 ;; These are just placeholders essentially.
806 (apply ,#'trace-call ,(make-trace-info) #() args))))))
807 (index (+ sb-vm:code-constants-offset sb-vm:code-slots-per-simple-fun)))
808 ;; First three args to APPLY must be at the expected offets
809 (aver (typep (code-header-ref c (+ index 0)) 'function))
810 (aver (typep (code-header-ref c (+ index 1)) 'trace-info))
811 (aver (typep (code-header-ref c (+ index 2)) 'simple-vector))
813 t)))
814 (index (+ sb-vm:code-constants-offset sb-vm:code-slots-per-simple-fun)))
815 (setf (code-header-ref code (+ index 0)) (symbol-function wrapper)
816 (code-header-ref code (+ index 1)) info
817 (code-header-ref code (+ index 2)) actual-fun)
818 (%code-entry-point code 0))
819 #-(or x86 x86-64)
820 (values (compile nil `(lambda (&rest args)
821 (apply #',wrapper ,info ,actual-fun args)))))
823 ;;; The usual ENCAPSULATE encapsulates NAME by changing what NAME points to,
824 ;;; that is, by altering the fdefinition.
825 ;;; In contrast, ENCAPSULATE-FUNOBJ encapsulates TRACED-FUN by changing the
826 ;;; entry point of the function to redirect to a tracing wrapper which then
827 ;;; calls back to the correct entry point.
828 (defun encapsulate-funobj (traced-fun &optional (name nil namep))
829 (declare (type (or simple-fun closure) traced-fun))
830 (let* ((proxy-fun
831 (typecase traced-fun
832 (simple-fun
833 ;; Generate a "closure" (that closes over nothing) which calls the
834 ;; original underlying function so that the original's entry point
835 ;; can be redirected to a tracing wrapper, which will produce trace
836 ;; output and invoke the closure which invokes the original fun.
837 #+(or x86-64 arm64)
838 (with-pinned-objects ((%closure-fun traced-fun))
839 (sb-vm::%alloc-closure 0 (sb-vm::%closure-callee traced-fun)))
840 #-(or x86-64 arm64) (%primitive sb-vm::make-closure traced-fun nil 0 nil))
841 (closure
842 ;; Same as above, but simpler - the original closure will redirect
843 ;; to the tracing wraper, which will invoke a new closure that is
844 ;; behaviorally identical to the original closure.
845 (sb-impl::copy-closure traced-fun))))
846 (info (make-trace-info :what (if namep name (%fun-name traced-fun))
847 :encapsulated t
848 :report 'trace))
849 (tracing-wrapper
850 (compile-funobj-encapsulation 'trace-call info proxy-fun)))
851 (with-pinned-objects (tracing-wrapper)
852 (let (#+(or x86 x86-64 arm64)
853 (tracing-wrapper-entry
854 (+ (get-lisp-obj-address tracing-wrapper)
855 (- sb-vm:fun-pointer-lowtag)
856 (ash sb-vm:simple-fun-insts-offset sb-vm:word-shift))))
857 (typecase traced-fun
858 (simple-fun
859 (let ((code (fun-code-header traced-fun)))
860 (set-tracing-bit code code-is-traced)
861 (let ((fun-header-word-index
862 (with-pinned-objects (code)
863 (let ((delta (- (get-lisp-obj-address traced-fun)
864 (get-lisp-obj-address code)
865 sb-vm:fun-pointer-lowtag
866 (- sb-vm:other-pointer-lowtag))))
867 (aver (not (logtest delta sb-vm:lowtag-mask)))
868 (ash delta (- sb-vm:word-shift))))))
869 ;; the entry point in CODE points to the tracing wrapper
870 (setf (code-header-ref code (1+ fun-header-word-index))
871 #+(or x86 x86-64 arm64) (make-lisp-obj tracing-wrapper-entry)
872 #-(or x86 x86-64 arm64) tracing-wrapper))))
873 (closure
874 (with-pinned-objects (traced-fun)
875 ;; redirect the original closure to the tracing wrapper
876 #+(or x86 x86-64 arm64)
877 (setf (sap-ref-word (int-sap (get-lisp-obj-address traced-fun))
878 (- sb-vm:n-word-bytes sb-vm:fun-pointer-lowtag))
879 tracing-wrapper-entry)
880 #-(or x86 x86-64 arm64)
881 (setf (sap-ref-lispobj (int-sap (get-lisp-obj-address traced-fun))
882 (- sb-vm:n-word-bytes sb-vm:fun-pointer-lowtag))
883 tracing-wrapper))))))
884 ;; Possibly update #'NAME to point to the tracing wrapper
885 (when (and namep (eq (fboundp name) traced-fun))
886 (setf (fdefn-fun (find-fdefn name)) tracing-wrapper))
887 tracing-wrapper))