1;;;; a tracing facility
2
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.
11
12(in-package "SB-DEBUG") ; (SB-, not SB!, since we're built in warm load.)
13
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..
17
18(defvar *trace-indentation-step* 2
19  #+sb-doc
20  "the increase in trace indentation at each call level")
21
22(defvar *max-trace-indentation* 40
23  #+sb-doc
24  "If the trace indentation exceeds this value, then indentation restarts at
25   0.")
26
27(defvar *trace-encapsulate-default* t
28  #+sb-doc
29  "the default value for the :ENCAPSULATE option to TRACE")
30
31;;;; internal state
32
33;;; a hash table that maps each traced function to the TRACE-INFO. The
34;;; entry for a closure is the shared function entry object.
35(defvar *traced-funs* (make-hash-table :test 'eq :synchronized t))
36
37(deftype trace-report-type ()
38  '(member nil trace))
39
40;;; A TRACE-INFO object represents all the information we need to
41;;; trace a given function.
42(def!struct (trace-info
43             (:print-object (lambda (x stream)
44                              (print-unreadable-object (x stream :type t)
45                                (prin1 (trace-info-what x) stream)))))
46  ;; the original representation of the thing traced
47  (what nil :type (or function cons symbol))
48  ;; Is WHAT a function name whose definition we should track?
49  (named nil)
50  ;; Is tracing to be done by encapsulation rather than breakpoints?
51  ;; T implies NAMED.
52  (encapsulated *trace-encapsulate-default*)
53  ;; Has this trace been untraced?
54  (untraced nil)
55  ;; breakpoints we set up to trigger tracing
56  (start-breakpoint nil :type (or sb-di:breakpoint null))
57  (end-breakpoint nil :type (or sb-di:breakpoint null))
58  ;; the list of function names for WHEREIN, or NIL if unspecified
59  (wherein nil :type list)
60  ;; should we trace methods given a generic function to trace?
61  (methods nil)
62
63  ;; The following slots represent the forms that we are supposed to
64  ;; evaluate on each iteration. Each form is represented by a cons
65  ;; (Form . Function), where the Function is the cached result of
66  ;; coercing Form to a function. Forms which use the current
67  ;; environment are converted with PREPROCESS-FOR-EVAL, which gives
68  ;; us a one-arg function. Null environment forms also have one-arg
69  ;; functions, but the argument is ignored. NIL means unspecified
70  ;; (the default.)
71
72  ;; report type
73  (report 'trace :type trace-report-type)
74  ;; current environment forms
75  (condition nil)
76  (break nil)
77  ;; List of current environment forms
78  (print () :type list)
79  ;; null environment forms
80  (condition-after nil)
81  (break-after nil)
82  ;; list of null environment forms
83  (print-after () :type list))
84(!set-load-form-method trace-info (:target))
85
86;;; This is a list of conses (fun-end-cookie . condition-satisfied),
87;;; which we use to note distinct dynamic entries into functions. When
88;;; we enter a traced function, we add a entry to this list holding
89;;; the new end-cookie and whether the trace condition was satisfied.
90;;; We must save the trace condition so that the after breakpoint
91;;; knows whether to print. The length of this list tells us the
92;;; indentation to use for printing TRACE messages.
93;;;
94;;; This list also helps us synchronize the TRACE facility dynamically
95;;; for detecting non-local flow of control. Whenever execution hits a
96;;; :FUN-END breakpoint used for TRACE'ing, we look for the
97;;; FUN-END-COOKIE at the top of *TRACED-ENTRIES*. If it is not
98;;; there, we discard any entries that come before our cookie.
99;;;
100;;; When we trace using encapsulation, we bind this variable and add
101;;; (NIL . CONDITION-SATISFIED), so a NIL "cookie" marks an
102;;; encapsulated tracing.
103(defvar *traced-entries* ())
104(declaim (list *traced-entries*))
105
106;;; This variable is used to discourage infinite recursions when some
107;;; trace action invokes a function that is itself traced. In this
108;;; case, we quietly ignore the inner tracing.
109(defvar *in-trace* nil)
110
111;;;; utilities
112
113;;; Given a function name, a function or a macro name, return the raw
114;;; definition and some information. "Raw" means that if the result is
115;;; a closure, we strip off the closure and return the bare code. The
116;;; second value is T if the argument was a function name. The third
117;;; value is one of :COMPILED, :COMPILED-CLOSURE, :INTERPRETED,
118;;; :INTERPRETED-CLOSURE and :FUNCALLABLE-INSTANCE.
119(defun trace-fdefinition (x)
120  (flet ((get-def ()
121           (if (valid-function-name-p x)
122               (if (fboundp x)
123                   (fdefinition x)
124                   (warn "~/sb-impl::print-symbol-with-prefix/ is ~
125                          undefined, not tracing." x))
126               (warn "~S is not a valid function name, not tracing." x))))
127    (multiple-value-bind (res named-p)
128        (typecase x
129         (symbol
130          (cond ((special-operator-p x)
131                 (warn "~S is a special operator, not tracing." x))
132                ((macro-function x))
133                (t
134                 (values (get-def) t))))
135         (function
136          x)
137         (t
138          (values (get-def) t)))
139     (typecase res
140       (closure
141        (values (sb-kernel:%closure-fun res)
142                named-p
143                :compiled-closure))
144       (funcallable-instance
145        (values res named-p :funcallable-instance))
146       ;; FIXME: What about SB!EVAL:INTERPRETED-FUNCTION -- it gets picked off
147       ;; by the FIN above, is that right?
148       (t
149        (values res named-p :compiled))))))
150
151;;; When a function name is redefined, and we were tracing that name,
152;;; then untrace the old definition and trace the new one.
153(defun trace-redefined-update (fname new-value)
154  (when (fboundp fname)
155    (let* ((fun (trace-fdefinition fname))
156           (info (gethash fun *traced-funs*)))
157      (when (and info (trace-info-named info))
158        (untrace-1 fname)
159        (trace-1 fname info new-value)))))
160(push #'trace-redefined-update *setf-fdefinition-hook*)
161
162;;; Annotate a FORM to evaluate with pre-converted functions. FORM is
163;;; really a cons (EXP . FUNCTION). LOC is the code location to use
164;;; for the lexical environment. If LOC is NIL, evaluate in the null
165;;; environment. If FORM is NIL, just return NIL.
166(defun coerce-form (form loc)
167  (when form
168    (let ((exp (car form)))
169      (if (sb-di:code-location-p loc)
170          (let ((fun (sb-di:preprocess-for-eval exp loc)))
171            (declare (type function fun))
172            (cons exp
173                  (lambda (frame &rest args)
174                    (declare (ignore args))
175                    (let ((*current-frame* frame))
176                      (funcall fun frame)))))
177          (let* ((body `(locally (declare (disable-package-locks sb-debug:arg))
178                          (flet ((sb-debug:arg (n)
179                                   (elt args n)))
180                            (declare (ignorable #'sb-debug:arg)
181                                     (enable-package-locks sb-debug:arg))
182                            ,exp)))
183                 (fun (coerce `(lambda (&rest args) (declare (ignorable args))
184                                 ,body) 'function)))
185            (cons exp
186                  (lambda (frame &rest args)
187                    (declare (ignore frame))
188                    (let ((*current-frame* nil))
189                      (apply fun args)))))))))
190
191(defun coerce-form-list (forms loc)
192  (mapcar (lambda (x) (coerce-form x loc)) forms))
193
194;;; Print indentation according to the number of trace entries.
195;;; Entries whose condition was false don't count.
196(defun print-trace-indentation ()
197  (let* ((depth (count-if #'cdr *traced-entries*))
198         (step *trace-indentation-step*)
199         (max *max-trace-indentation*)
200         (indent (+ (mod (* depth step) (- max step)) step)))
201    (format t "~V,0@T~W: " indent depth)))
202
203;;; Return true if any of the NAMES appears on the stack below FRAME.
204(defun trace-wherein-p (frame names)
205  (do ((frame (sb-di:frame-down frame) (sb-di:frame-down frame)))
206      ((not frame) nil)
207    (when (member (sb-di:debug-fun-name (sb-di:frame-debug-fun frame))
208                  names
209                  :test #'equal)
210      (return t))))
211
212;;; Handle PRINT and PRINT-AFTER options.
213(defun trace-print (frame forms &rest args)
214  (dolist (ele forms)
215    (fresh-line)
216    (print-trace-indentation)
217    (format t "~@<~S ~_= ~:[; No values~;~:*~{~S~^, ~}~]~:>"
218            (car ele)
219            (multiple-value-list (apply (cdr ele) frame args)))
220    (terpri)))
221
222;;; Handle PRINT and PRINT-AFTER options when :REPORT style is NIL.
223(defun trace-print-unadorned (frame forms &rest args)
224  (dolist (ele forms)
225    (let ((values (multiple-value-list (apply (cdr ele) frame args))))
226      (when values
227        (format t "~&~{~A~^, ~}~%" values)))))
228
229;;; Test a BREAK option, and if true, break.
230(defun trace-maybe-break (info break where frame &rest args)
231  (when (and break (apply (cdr break) frame args))
232    (sb-di:flush-frames-above frame)
233    (let ((*stack-top-hint* frame))
234      (break "breaking ~A traced call to ~S:"
235             where
236             (trace-info-what info)))))
237
238;;; Discard any invalid cookies on our simulated stack. Encapsulated
239;;; entries are always valid, since we bind *TRACED-ENTRIES* in the
240;;; encapsulation.
241(defun discard-invalid-entries (frame)
242  (loop
243    (when (or (null *traced-entries*)
244              (let ((cookie (caar *traced-entries*)))
245                (or (not cookie)
246                    (sb-di:fun-end-cookie-valid-p frame cookie))))
247      (return))
248    (pop *traced-entries*)))
249
250;;;; hook functions
251
252;;; Return a closure that can be used for a function start breakpoint
253;;; hook function and a closure that can be used as the FUN-END-COOKIE
254;;; function. The first communicates the sense of the
255;;; TRACE-INFO-CONDITION to the second via a closure variable.
256(defun trace-start-breakpoint-fun (info)
257  (let (conditionp)
258    (values
259     (lambda (frame bpt &rest args)
260       (declare (ignore bpt))
261       (discard-invalid-entries frame)
262       (let ((condition (trace-info-condition info))
263             (wherein (trace-info-wherein info)))
264         (setq conditionp
265               (and (not *in-trace*)
266                    (or (not condition)
267                        (apply (cdr condition) frame args))
268                    (or (not wherein)
269                        (trace-wherein-p frame wherein)))))
270       (when conditionp
271         (let ((sb-kernel:*current-level-in-print* 0)
272               (*standard-output* (make-string-output-stream))
273               (*in-trace* t))
274           (ecase (trace-info-report info)
275             (trace
276              (fresh-line)
277              (print-trace-indentation)
278              (if (trace-info-encapsulated info)
279                  (prin1 `(,(trace-info-what info)
280                            ,@(mapcar #'ensure-printable-object args)))
281                  (print-frame-call frame *standard-output*))
282              (terpri)
283              (apply #'trace-print frame (trace-info-print info) args))
284             ((nil)
285              (apply #'trace-print-unadorned frame (trace-info-print info) args)))
286           (write-sequence (get-output-stream-string *standard-output*)
287                           *trace-output*)
288           (finish-output *trace-output*))
289         (apply #'trace-maybe-break info (trace-info-break info) "before"
290                frame args)))
291     (lambda (frame cookie)
292       (declare (ignore frame))
293       (push (cons cookie conditionp) *traced-entries*)))))
294
295;;; This prints a representation of the return values delivered.
296;;; First, this checks to see that cookie is at the top of
297;;; *TRACED-ENTRIES*; if it is not, then we need to adjust this list
298;;; to determine the correct indentation for output. We then check to
299;;; see whether the function is still traced and that the condition
300;;; succeeded before printing anything.
301(declaim (ftype (function (trace-info) function) trace-end-breakpoint-fun))
302(defun trace-end-breakpoint-fun (info)
303  (lambda (frame bpt values cookie)
304    (declare (ignore bpt))
305    (unless (eq cookie (caar *traced-entries*))
306      (setf *traced-entries*
307            (member cookie *traced-entries* :key #'car)))
308
309    (let ((entry (pop *traced-entries*)))
310      (when (and (not (trace-info-untraced info))
311                 (or (cdr entry)
312                     (let ((cond (trace-info-condition-after info)))
313                       (and cond (apply #'funcall (cdr cond) frame values)))))
314        (let ((sb-kernel:*current-level-in-print* 0)
315              (*standard-output* (make-string-output-stream))
316              (*in-trace* t))
317          (ecase (trace-info-report info)
318            (trace
319             (fresh-line)
320             (let ((*print-pretty* t))
321               (pprint-logical-block (*standard-output* nil)
322                 (print-trace-indentation)
323                 (pprint-indent :current 2)
324                 (format t "~S returned" (trace-info-what info))
325                 (dolist (v values)
326                   (write-char #\space)
327                   (pprint-newline :linear)
328                   (prin1 (ensure-printable-object v))))
329               (terpri))
330             (apply #'trace-print frame (trace-info-print-after info) values))
331            ((nil)
332             (apply #'trace-print-unadorned frame (trace-info-print-after info) values)))
333          (write-sequence (get-output-stream-string *standard-output*)
334                          *trace-output*)
335          (finish-output *trace-output*))
336        (apply #'trace-maybe-break info (trace-info-break-after info) "after"
337               frame values)))))
338
339;;; This function is called by the trace encapsulation. It calls the
340;;; breakpoint hook functions with NIL for the breakpoint and cookie,
341;;; which we have cleverly contrived to work for our hook functions.
342(defun trace-call (info function &rest args)
343  (multiple-value-bind (start cookie) (trace-start-breakpoint-fun info)
344    (declare (type function start cookie))
345    (let ((frame (sb-di:frame-down (sb-di:top-frame))))
346      (apply #'funcall start frame nil args)
347      (let ((*traced-entries* *traced-entries*))
348        (funcall cookie frame nil)
349        (let ((vals (multiple-value-list (apply function args))))
350          (funcall (trace-end-breakpoint-fun info) frame nil vals nil)
351          (values-list vals))))))
352
353;;; Trace one function according to the specified options. We copy the
354;;; trace info (it was a quoted constant), fill in the functions, and
355;;; then install the breakpoints or encapsulation.
356;;;
357;;; If non-null, DEFINITION is the new definition of a function that
358;;; we are automatically retracing.
359(defun trace-1 (function-or-name info &optional definition)
360  (multiple-value-bind (fun named kind)
361      (if definition
362          (values definition t
363                  (nth-value 2 (trace-fdefinition definition)))
364          (trace-fdefinition function-or-name))
365    (when fun
366      (when (gethash fun *traced-funs*)
367        (warn "~S is already TRACE'd, untracing it first." function-or-name)
368        (untrace-1 fun))
369      (let* ((debug-fun (sb-di:fun-debug-fun fun))
370             (encapsulated
371              (if (eq (trace-info-encapsulated info) :default)
372                  (ecase kind
373                    (:compiled nil)
374                    (:compiled-closure
375                     (unless (functionp function-or-name)
376                       (warn "tracing shared code for ~S:~%  ~S"
377                             function-or-name
378                             fun))
379                     nil)
380                    ((:interpreted :interpreted-closure :funcallable-instance)
381                     t))
382                  (trace-info-encapsulated info)))
383             (loc (if encapsulated
384                      :encapsulated
385                      (sb-di:debug-fun-start-location debug-fun)))
386             (info (make-trace-info
387                    :what function-or-name
388                    :named named
389                    :encapsulated encapsulated
390                    :wherein (trace-info-wherein info)
391                    :methods (trace-info-methods info)
392                    :condition (coerce-form (trace-info-condition info) loc)
393                    :break (coerce-form (trace-info-break info) loc)
394                    :report (trace-info-report info)
395                    :print (coerce-form-list (trace-info-print info) loc)
396                    :break-after (coerce-form (trace-info-break-after info) nil)
397                    :condition-after
398                    (coerce-form (trace-info-condition-after info) nil)
399                    :print-after
400                    (coerce-form-list (trace-info-print-after info) nil))))
401
402        (dolist (wherein (trace-info-wherein info))
403          (unless (or (stringp wherein)
404                      (fboundp wherein))
405            (warn ":WHEREIN name ~S is not a defined global function."
406                  wherein)))
407
408        (cond
409          (encapsulated
410           (unless named
411             (error "can't use encapsulation to trace anonymous function ~S"
412                    fun))
413           (encapsulate function-or-name 'trace
414                        (lambda (function &rest args)
415                          (apply #'trace-call info function args))))
416          (t
417           (multiple-value-bind (start-fun cookie-fun)
418               (trace-start-breakpoint-fun info)
419             (let ((start (sb-di:make-breakpoint start-fun debug-fun
420                                                 :kind :fun-start))
421                   (end (sb-di:make-breakpoint
422                         (trace-end-breakpoint-fun info)
423                         debug-fun :kind :fun-end
424                         :fun-end-cookie cookie-fun)))
425               (setf (trace-info-start-breakpoint info) start)
426               (setf (trace-info-end-breakpoint info) end)
427               ;; The next two forms must be in the order in which they
428               ;; appear, since the start breakpoint must run before the
429               ;; fun-end breakpoint's start helper (which calls the
430               ;; cookie function.) One reason is that cookie function
431               ;; requires that the CONDITIONP shared closure variable be
432               ;; initialized.
433               (sb-di:activate-breakpoint start)
434               (sb-di:activate-breakpoint end)))))
435
436        (setf (gethash fun *traced-funs*) info))
437
438      (when (and (typep fun 'generic-function)
439                 (trace-info-methods info)
440                 ;; we are going to trace the method functions directly.
441                 (not (trace-info-encapsulated info)))
442        (dolist (method (sb-mop:generic-function-methods fun))
443          (let ((mf (sb-mop:method-function method)))
444            ;; NOTE: this direct style of tracing methods -- tracing the
445            ;; pcl-internal method functions -- is only one possible
446            ;; alternative.  It fails (a) when encapulation is
447            ;; requested, because the function objects themselves are
448            ;; stored in the method object; (b) when the method in
449            ;; question is particularly simple, when the method
450            ;; functionality is in the dfun.  See src/pcl/env.lisp for a
451            ;; stub implementation of encapsulating through a
452            ;; traced-method class.
453            (trace-1 mf info)
454            (when (typep mf 'sb-pcl::%method-function)
455              (trace-1 (sb-pcl::%method-function-fast-function mf) info)))))
456
457      function-or-name)))
458
459;;;; the TRACE macro
460
461;;; Parse leading trace options off of SPECS, modifying INFO
462;;; accordingly. The remaining portion of the list is returned when we
463;;; encounter a plausible function name.
464(defun parse-trace-options (specs info)
465  (let ((current specs))
466    (loop
467      (when (endp current) (return))
468      (let ((option (first current))
469            (value (cons (second current) nil)))
470        (case option
471          (:report
472           (unless (typep (car value) 'trace-report-type)
473             (error "~S is not a valid ~A ~S type."
474                    (car value) 'trace :report))
475           (setf (trace-info-report info) (car value)))
476          (:condition (setf (trace-info-condition info) value))
477          (:condition-after
478           (setf (trace-info-condition info) (cons nil nil))
479           (setf (trace-info-condition-after info) value))
480          (:condition-all
481           (setf (trace-info-condition info) value)
482           (setf (trace-info-condition-after info) value))
483          (:wherein
484           (setf (trace-info-wherein info)
485                 (if (listp (car value)) (car value) value)))
486          (:encapsulate
487           (setf (trace-info-encapsulated info) (car value)))
488          (:methods
489           (setf (trace-info-methods info) (car value)))
490          (:break (setf (trace-info-break info) value))
491          (:break-after (setf (trace-info-break-after info) value))
492          (:break-all
493           (setf (trace-info-break info) value)
494           (setf (trace-info-break-after info) value))
495          (:print
496           (setf (trace-info-print info)
497                 (append (trace-info-print info) (list value))))
498          (:print-after
499           (setf (trace-info-print-after info)
500                 (append (trace-info-print-after info) (list value))))
501          (:print-all
502           (setf (trace-info-print info)
503                 (append (trace-info-print info) (list value)))
504           (setf (trace-info-print-after info)
505                 (append (trace-info-print-after info) (list value))))
506          (t (return)))
507        (pop current)
508        (unless current
509          (error "missing argument to ~S TRACE option" option))
510        (pop current)))
511    current))
512
513;;; Compute the expansion of TRACE in the non-trivial case (arguments
514;;; specified.)
515(defun expand-trace (specs)
516  (collect ((binds)
517            (forms))
518    (let* ((global-options (make-trace-info))
519           (current (parse-trace-options specs global-options)))
520      (loop
521        (when (endp current) (return))
522        (let ((name (pop current))
523              (options (copy-trace-info global-options)))
524          (cond
525           ((eq name :function)
526            (let ((temp (gensym)))
527              (binds `(,temp ,(pop current)))
528              (forms `(trace-1 ,temp ',options))))
529           ((and (keywordp name)
530                 (not (or (fboundp name) (macro-function name))))
531            (error "unknown TRACE option: ~S" name))
532           ((stringp name)
533            (let ((package (find-undeleted-package-or-lose name)))
534              (do-all-symbols (symbol (find-package name))
535                (when (eql package (symbol-package symbol))
536                  (when (and (fboundp symbol)
537                             (not (macro-function symbol))
538                             (not (special-operator-p symbol)))
539                    (forms `(trace-1 ',symbol ',options)))
540                  (let ((setf-name `(setf ,symbol)))
541                    (when (fboundp setf-name)
542                      (forms `(trace-1 ',setf-name ',options))))))))
543           ;; special-case METHOD: it itself is not a general function
544           ;; name symbol, but it (at least here) designates one of a
545           ;; pair of such.
546           ((and (consp name) (eq (car name) 'method))
547            (when (fboundp (list* 'sb-pcl::slow-method (cdr name)))
548              (forms `(trace-1 ',(list* 'sb-pcl::slow-method (cdr name))
549                               ',options)))
550            (when (fboundp (list* 'sb-pcl::fast-method (cdr name)))
551              (forms `(trace-1 ',(list* 'sb-pcl::fast-method (cdr name))
552                               ',options))))
553           (t
554            (forms `(trace-1 ',name ',options))))
555          (setq current (parse-trace-options current options)))))
556
557    `(let ,(binds)
558       (remove nil (list ,@(forms))))))
559
560(defun %list-traced-funs ()
561  (loop for x being each hash-value in *traced-funs*
562        collect (trace-info-what x)))
563
564(defmacro trace (&rest specs)
565  #+sb-doc
566  "TRACE {Option Global-Value}* {Name {Option Value}*}*
567
568TRACE is a debugging tool that provides information when specified
569functions are called. In its simplest form:
570
571       (TRACE NAME-1 NAME-2 ...)
572
573The NAMEs are not evaluated. Each may be a symbol, denoting an
574individual function, or a string, denoting all functions fbound to
575symbols whose home package is the package with the given name.
576
577Options allow modification of the default behavior. Each option is a
578pair of an option keyword and a value form. Global options are
579specified before the first name, and affect all functions traced by a
580given use of TRACE. Options may also be interspersed with function
581names, in which case they act as local options, only affecting tracing
582of the immediately preceding function name. Local options override
583global options.
584
585By default, TRACE causes a printout on *TRACE-OUTPUT* each time that
586one of the named functions is entered or returns. (This is the basic,
587ANSI Common Lisp behavior of TRACE.)
588
589The following options are defined:
590
591   :REPORT Report-Type
592       If Report-Type is TRACE (the default) then information is
593       reported by printing immediately. If Report-Type is NIL, then
594       the only effect of the trace is to execute other
595       options (e.g. PRINT or BREAK).
596
597   :CONDITION Form
598   :CONDITION-AFTER Form
599   :CONDITION-ALL Form
600       If :CONDITION is specified, then TRACE does nothing unless Form
601       evaluates to true at the time of the call. :CONDITION-AFTER is
602       similar, but suppresses the initial printout, and is tested when the
603       function returns. :CONDITION-ALL tries both before and after.
604
605   :BREAK Form
606   :BREAK-AFTER Form
607   :BREAK-ALL Form
608       If specified, and Form evaluates to true, then the debugger is invoked
609       at the start of the function, at the end of the function, or both,
610       according to the respective option.
611
612   :PRINT Form
613   :PRINT-AFTER Form
614   :PRINT-ALL Form
615       In addition to the usual printout, the result of evaluating Form is
616       printed at the start of the function, at the end of the function, or
617       both, according to the respective option. Multiple print options cause
618       multiple values to be printed.
619
620   :WHEREIN Names
621       If specified, Names is a function name or list of names. TRACE does
622       nothing unless a call to one of those functions encloses the call to
623       this function (i.e. it would appear in a backtrace.)  Anonymous
624       functions have string names like \"DEFUN FOO\".
625
626   :ENCAPSULATE {:DEFAULT | T | NIL}
627       If T, the tracing is done via encapsulation (redefining the function
628       name) rather than by modifying the function. :DEFAULT is the default,
629       and means to use encapsulation for interpreted functions and funcallable
630       instances, breakpoints otherwise. When encapsulation is used, forms are
631       *not* evaluated in the function's lexical environment, but SB-DEBUG:ARG
632       can still be used.
633
634   :METHODS {T | NIL}
635       If T, any function argument naming a generic function will have its
636       methods traced in addition to the generic function itself.
637
638   :FUNCTION Function-Form
639       This is a not really an option, but rather another way of specifying
640       what function to trace. The Function-Form is evaluated immediately,
641       and the resulting function is traced.
642
643:CONDITION, :BREAK and :PRINT forms are evaluated in a context which
644mocks up the lexical environment of the called function, so that
645SB-DEBUG:VAR and SB-DEBUG:ARG can be used.
646The -AFTER and -ALL forms can use SB-DEBUG:ARG."
647  (if specs
648      (expand-trace specs)
649      '(%list-traced-funs)))
650
651;;;; untracing
652
653;;; Untrace one function.
654(defun untrace-1 (function-or-name)
655  (let* ((fun (trace-fdefinition function-or-name))
656         (info (when fun (gethash fun *traced-funs*))))
657    (cond
658      ((and fun (not info))
659       (warn "Function is not TRACEd: ~S" function-or-name))
660      ((not fun)
661       ;; Someone has FMAKUNBOUND it.
662       (let ((table *traced-funs*))
663         (with-locked-system-table (table)
664           (maphash (lambda (fun info)
665                      (when (equal function-or-name (trace-info-what info))
666                        (remhash fun table)))
667                    table))))
668      (t
669       (cond
670         ((trace-info-encapsulated info)
671          (unencapsulate (trace-info-what info) 'trace))
672         (t
673          (sb-di:delete-breakpoint (trace-info-start-breakpoint info))
674          (sb-di:delete-breakpoint (trace-info-end-breakpoint info))))
675       (setf (trace-info-untraced info) t)
676       (remhash fun *traced-funs*)))))
677
678;;; Untrace all traced functions.
679(defun untrace-all ()
680  (dolist (fun (%list-traced-funs))
681    (untrace-1 fun))
682  t)
683
684(defun untrace-package (name)
685  (let ((package (find-package name)))
686    (when package
687      (dolist (fun (%list-traced-funs))
688        (cond ((and (symbolp fun) (eq package (symbol-package fun)))
689               (untrace-1 fun))
690              ((and (consp fun) (eq 'setf (car fun))
691                    (symbolp (second fun))
692                    (eq package (symbol-package (second fun))))
693               (untrace-1 fun)))))))
694
695(defmacro untrace (&rest specs)
696  #+sb-doc
697  "Remove tracing from the specified functions. Untraces all
698functions when called with no arguments."
699  (if specs
700      `(progn
701         ,@(loop while specs
702                 for name = (pop specs)
703                 collect (cond ((eq name :function)
704                                `(untrace-1 ,(pop specs)))
705                               ((stringp name)
706                                `(untrace-package ,name))
707                               (t
708                                `(untrace-1 ',name))))
709         t)
710      '(untrace-all)))
711