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