Fix make-array transforms.
[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 :synchronized t))
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   ;; should we trace methods given a generic function to trace?
64   (methods nil)
65
66   ;; The following slots represent the forms that we are supposed to
67   ;; evaluate on each iteration. Each form is represented by a cons
68   ;; (Form . Function), where the Function is the cached result of
69   ;; coercing Form to a function. Forms which use the current
70   ;; environment are converted with PREPROCESS-FOR-EVAL, which gives
71   ;; us a one-arg function. Null environment forms also have one-arg
72   ;; functions, but the argument is ignored. NIL means unspecified
73   ;; (the default.)
74
75   ;; current environment forms
76   (condition nil)
77   (break nil)
78   ;; List of current environment forms
79   (print () :type list)
80   ;; null environment forms
81   (condition-after nil)
82   (break-after nil)
83   ;; list of null environment forms
84   (print-after () :type list))
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 \f
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)
174                     (let ((*current-frame* frame))
175                       (funcall fun frame)))))
176           (let* ((bod (ecase loc
177                         ((nil) exp)
178                         (:encapsulated
179                          `(locally (declare (disable-package-locks sb-debug:arg arg-list))
180                            (flet ((sb-debug:arg (n)
181                                     (declare (special arg-list))
182                                     (elt arg-list n)))
183                              (declare (ignorable #'sb-debug:arg)
184                                       (enable-package-locks sb-debug:arg arg-list))
185                              ,exp)))))
186                  (fun (coerce `(lambda () ,bod) 'function)))
187             (cons exp
188                   (lambda (frame)
189                     (declare (ignore frame))
190                     (let ((*current-frame* nil))
191                       (funcall fun)))))))))
192
193 (defun coerce-form-list (forms loc)
194   (mapcar (lambda (x) (coerce-form x loc)) forms))
195
196 ;;; Print indentation according to the number of trace entries.
197 ;;; Entries whose condition was false don't count.
198 (defun print-trace-indentation ()
199   (let ((depth 0))
200     (dolist (entry *traced-entries*)
201       (when (cdr entry) (incf depth)))
202     (format t
203             "~V,0@T~W: "
204             (+ (mod (* depth *trace-indentation-step*)
205                     (- *max-trace-indentation* *trace-indentation-step*))
206                *trace-indentation-step*)
207             depth)))
208
209 ;;; Return true if any of the NAMES appears on the stack below FRAME.
210 (defun trace-wherein-p (frame names)
211   (do ((frame (sb-di:frame-down frame) (sb-di:frame-down frame)))
212       ((not frame) nil)
213     (when (member (sb-di:debug-fun-name (sb-di:frame-debug-fun frame))
214                   names
215                   :test #'equal)
216       (return t))))
217
218 ;;; Handle PRINT and PRINT-AFTER options.
219 (defun trace-print (frame forms)
220   (dolist (ele forms)
221     (fresh-line)
222     (print-trace-indentation)
223     (format t "~@<~S ~_= ~:[; No values~;~:*~{~S~^, ~}~]~:>"
224             (car ele)
225             (multiple-value-list (funcall (cdr ele) frame)))
226     (terpri)))
227
228 ;;; Test a BREAK option, and if true, break.
229 (defun trace-maybe-break (info break where frame)
230   (when (and break (funcall (cdr break) frame))
231     (sb-di:flush-frames-above frame)
232     (let ((*stack-top-hint* frame))
233       (break "breaking ~A traced call to ~S:"
234              where
235              (trace-info-what info)))))
236
237 ;;; Discard any invalid cookies on our simulated stack. Encapsulated
238 ;;; entries are always valid, since we bind *TRACED-ENTRIES* in the
239 ;;; encapsulation.
240 (defun discard-invalid-entries (frame)
241   (loop
242     (when (or (null *traced-entries*)
243               (let ((cookie (caar *traced-entries*)))
244                 (or (not cookie)
245                     (sb-di:fun-end-cookie-valid-p frame cookie))))
246       (return))
247     (pop *traced-entries*)))
248 \f
249 ;;;; hook functions
250
251 ;;; Return a closure that can be used for a function start breakpoint
252 ;;; hook function and a closure that can be used as the FUN-END-COOKIE
253 ;;; function. The first communicates the sense of the
254 ;;; TRACE-INFO-CONDITION to the second via a closure variable.
255 (defun trace-start-breakpoint-fun (info)
256   (let (conditionp)
257     (values
258
259      (lambda (frame bpt)
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                         (funcall (cdr condition) frame))
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            (fresh-line)
275            (print-trace-indentation)
276            (if (trace-info-encapsulated info)
277                ;; FIXME: These special variables should be given
278                ;; *FOO*-style names, and probably declared globally
279                ;; with DEFVAR.
280                (locally
281                  (declare (special basic-definition arg-list))
282                  (prin1 `(,(trace-info-what info)
283                           ,@(mapcar #'ensure-printable-object arg-list))))
284                (print-frame-call frame *standard-output*))
285            (terpri)
286            (trace-print frame (trace-info-print info))
287            (write-sequence (get-output-stream-string *standard-output*)
288                            *trace-output*)
289            (finish-output *trace-output*))
290          (trace-maybe-break info (trace-info-break info) "before" frame)))
291
292      (lambda (frame cookie)
293        (declare (ignore frame))
294        (push (cons cookie conditionp) *traced-entries*)))))
295
296 ;;; This prints a representation of the return values delivered.
297 ;;; First, this checks to see that cookie is at the top of
298 ;;; *TRACED-ENTRIES*; if it is not, then we need to adjust this list
299 ;;; to determine the correct indentation for output. We then check to
300 ;;; see whether the function is still traced and that the condition
301 ;;; succeeded before printing anything.
302 (declaim (ftype (function (trace-info) function) trace-end-breakpoint-fun))
303 (defun trace-end-breakpoint-fun (info)
304   (lambda (frame bpt *trace-values* cookie)
305     (declare (ignore bpt))
306     (unless (eq cookie (caar *traced-entries*))
307       (setf *traced-entries*
308             (member cookie *traced-entries* :key #'car)))
309
310     (let ((entry (pop *traced-entries*)))
311       (when (and (not (trace-info-untraced info))
312                  (or (cdr entry)
313                      (let ((cond (trace-info-condition-after info)))
314                        (and cond (funcall (cdr cond) frame)))))
315         (let ((sb-kernel:*current-level-in-print* 0)
316               (*standard-output* (make-string-output-stream))
317               (*in-trace* t))
318           (fresh-line)
319           (let ((*print-pretty* t))
320             (pprint-logical-block (*standard-output* nil)
321               (print-trace-indentation)
322               (pprint-indent :current 2)
323               (format t "~S returned" (trace-info-what info))
324               (dolist (v *trace-values*)
325                 (write-char #\space)
326                 (pprint-newline :linear)
327                 (prin1 (ensure-printable-object v))))
328             (terpri))
329           (trace-print frame (trace-info-print-after info))
330           (write-sequence (get-output-stream-string *standard-output*)
331                           *trace-output*)
332           (finish-output *trace-output*))
333         (trace-maybe-break info
334                            (trace-info-break-after info)
335                            "after"
336                            frame)))))
337 \f
338 ;;; This function is called by the trace encapsulation. It calls the
339 ;;; breakpoint hook functions with NIL for the breakpoint and cookie,
340 ;;; which we have cleverly contrived to work for our hook functions.
341 (defun trace-call (info)
342   (multiple-value-bind (start cookie) (trace-start-breakpoint-fun info)
343     (declare (type function start cookie))
344     (let ((frame (sb-di:frame-down (sb-di:top-frame))))
345       (funcall start frame nil)
346       (let ((*traced-entries* *traced-entries*))
347         (declare (special basic-definition arg-list))
348         (funcall cookie frame nil)
349         (let ((vals
350                (multiple-value-list
351                 (apply basic-definition arg-list))))
352           (funcall (trace-end-breakpoint-fun info) frame nil vals nil)
353           (values-list vals))))))
354 \f
355 ;;; Trace one function according to the specified options. We copy the
356 ;;; trace info (it was a quoted constant), fill in the functions, and
357 ;;; then install the breakpoints or encapsulation.
358 ;;;
359 ;;; If non-null, DEFINITION is the new definition of a function that
360 ;;; we are automatically retracing.
361 (defun trace-1 (function-or-name info &optional definition)
362   (multiple-value-bind (fun named kind)
363       (if definition
364           (values definition t
365                   (nth-value 2 (trace-fdefinition definition)))
366           (trace-fdefinition function-or-name))
367     (when fun
368       (when (gethash fun *traced-funs*)
369         (warn "~S is already TRACE'd, untracing it first." function-or-name)
370         (untrace-1 fun))
371       (let* ((debug-fun (sb-di:fun-debug-fun fun))
372              (encapsulated
373               (if (eq (trace-info-encapsulated info) :default)
374                   (ecase kind
375                     (:compiled nil)
376                     (:compiled-closure
377                      (unless (functionp function-or-name)
378                        (warn "tracing shared code for ~S:~%  ~S"
379                              function-or-name
380                              fun))
381                      nil)
382                     ((:interpreted :interpreted-closure :funcallable-instance)
383                      t))
384                   (trace-info-encapsulated info)))
385              (loc (if encapsulated
386                       :encapsulated
387                       (sb-di:debug-fun-start-location debug-fun)))
388              (info (make-trace-info
389                     :what function-or-name
390                     :named named
391                     :encapsulated encapsulated
392                     :wherein (trace-info-wherein info)
393                     :methods (trace-info-methods info)
394                     :condition (coerce-form (trace-info-condition info) loc)
395                     :break (coerce-form (trace-info-break info) loc)
396                     :print (coerce-form-list (trace-info-print info) loc)
397                     :break-after (coerce-form (trace-info-break-after info) nil)
398                     :condition-after
399                     (coerce-form (trace-info-condition-after info) nil)
400                     :print-after
401                     (coerce-form-list (trace-info-print-after info) nil))))
402
403         (dolist (wherein (trace-info-wherein info))
404           (unless (or (stringp wherein)
405                       (fboundp wherein))
406             (warn ":WHEREIN name ~S is not a defined global function."
407                   wherein)))
408
409         (cond
410           (encapsulated
411            (unless named
412              (error "can't use encapsulation to trace anonymous function ~S"
413                     fun))
414            (encapsulate function-or-name 'trace `(trace-call ',info)))
415           (t
416            (multiple-value-bind (start-fun cookie-fun)
417                (trace-start-breakpoint-fun info)
418              (let ((start (sb-di:make-breakpoint start-fun debug-fun
419                                                  :kind :fun-start))
420                    (end (sb-di:make-breakpoint
421                          (trace-end-breakpoint-fun info)
422                          debug-fun :kind :fun-end
423                          :fun-end-cookie cookie-fun)))
424                (setf (trace-info-start-breakpoint info) start)
425                (setf (trace-info-end-breakpoint info) end)
426                ;; The next two forms must be in the order in which they
427                ;; appear, since the start breakpoint must run before the
428                ;; fun-end breakpoint's start helper (which calls the
429                ;; cookie function.) One reason is that cookie function
430                ;; requires that the CONDITIONP shared closure variable be
431                ;; initialized.
432                (sb-di:activate-breakpoint start)
433                (sb-di:activate-breakpoint end)))))
434
435         (setf (gethash fun *traced-funs*) info))
436
437       (when (and (typep fun 'generic-function)
438                  (trace-info-methods info)
439                  ;; we are going to trace the method functions directly.
440                  (not (trace-info-encapsulated info)))
441         (dolist (method (sb-mop:generic-function-methods fun))
442           (let ((mf (sb-mop:method-function method)))
443             ;; NOTE: this direct style of tracing methods -- tracing the
444             ;; pcl-internal method functions -- is only one possible
445             ;; alternative.  It fails (a) when encapulation is
446             ;; requested, because the function objects themselves are
447             ;; stored in the method object; (b) when the method in
448             ;; question is particularly simple, when the method
449             ;; functionality is in the dfun.  See src/pcl/env.lisp for a
450             ;; stub implementation of encapsulating through a
451             ;; traced-method class.
452             (trace-1 mf info)
453             (when (typep mf 'sb-pcl::%method-function)
454               (trace-1 (sb-pcl::%method-function-fast-function mf) info)))))
455
456       function-or-name)))
457 \f
458 ;;;; the TRACE macro
459
460 ;;; Parse leading trace options off of SPECS, modifying INFO
461 ;;; accordingly. The remaining portion of the list is returned when we
462 ;;; encounter a plausible function name.
463 (defun parse-trace-options (specs info)
464   (let ((current specs))
465     (loop
466       (when (endp current) (return))
467       (let ((option (first current))
468             (value (cons (second current) nil)))
469         (case option
470           (:report (error "stub: The :REPORT option is not yet implemented."))
471           (:condition (setf (trace-info-condition info) value))
472           (:condition-after
473            (setf (trace-info-condition info) (cons nil nil))
474            (setf (trace-info-condition-after info) value))
475           (:condition-all
476            (setf (trace-info-condition info) value)
477            (setf (trace-info-condition-after info) value))
478           (:wherein
479            (setf (trace-info-wherein info)
480                  (if (listp (car value)) (car value) value)))
481           (:encapsulate
482            (setf (trace-info-encapsulated info) (car value)))
483           (:methods
484            (setf (trace-info-methods info) (car value)))
485           (:break (setf (trace-info-break info) value))
486           (:break-after (setf (trace-info-break-after info) value))
487           (:break-all
488            (setf (trace-info-break info) value)
489            (setf (trace-info-break-after info) value))
490           (:print
491            (setf (trace-info-print info)
492                  (append (trace-info-print info) (list value))))
493           (:print-after
494            (setf (trace-info-print-after info)
495                  (append (trace-info-print-after info) (list value))))
496           (:print-all
497            (setf (trace-info-print info)
498                  (append (trace-info-print info) (list value)))
499            (setf (trace-info-print-after info)
500                  (append (trace-info-print-after info) (list value))))
501           (t (return)))
502         (pop current)
503         (unless current
504           (error "missing argument to ~S TRACE option" option))
505         (pop current)))
506     current))
507
508 ;;; Compute the expansion of TRACE in the non-trivial case (arguments
509 ;;; specified.)
510 (defun expand-trace (specs)
511   (collect ((binds)
512             (forms))
513     (let* ((global-options (make-trace-info))
514            (current (parse-trace-options specs global-options)))
515       (loop
516         (when (endp current) (return))
517         (let ((name (pop current))
518               (options (copy-trace-info global-options)))
519           (cond
520            ((eq name :function)
521             (let ((temp (gensym)))
522               (binds `(,temp ,(pop current)))
523               (forms `(trace-1 ,temp ',options))))
524            ((and (keywordp name)
525                  (not (or (fboundp name) (macro-function name))))
526             (error "unknown TRACE option: ~S" name))
527            ((stringp name)
528             (let ((package (find-undeleted-package-or-lose name)))
529               (do-all-symbols (symbol (find-package name))
530                 (when (eql package (symbol-package symbol))
531                   (when (and (fboundp symbol)
532                              (not (macro-function symbol))
533                              (not (special-operator-p symbol)))
534                     (forms `(trace-1 ',symbol ',options)))
535                   (let ((setf-name `(setf ,symbol)))
536                     (when (fboundp setf-name)
537                       (forms `(trace-1 ',setf-name ',options))))))))
538            ;; special-case METHOD: it itself is not a general function
539            ;; name symbol, but it (at least here) designates one of a
540            ;; pair of such.
541            ((and (consp name) (eq (car name) 'method))
542             (when (fboundp (list* 'sb-pcl::slow-method (cdr name)))
543               (forms `(trace-1 ',(list* 'sb-pcl::slow-method (cdr name))
544                                ',options)))
545             (when (fboundp (list* 'sb-pcl::fast-method (cdr name)))
546               (forms `(trace-1 ',(list* 'sb-pcl::fast-method (cdr name))
547                                ',options))))
548            (t
549             (forms `(trace-1 ',name ',options))))
550           (setq current (parse-trace-options current options)))))
551
552     `(let ,(binds)
553        (remove nil (list ,@(forms))))))
554
555 (defun %list-traced-funs ()
556   (loop for x being each hash-value in *traced-funs*
557         collect (trace-info-what x)))
558
559 (defmacro trace (&rest specs)
560   #+sb-doc
561   "TRACE {Option Global-Value}* {Name {Option Value}*}*
562
563 TRACE is a debugging tool that provides information when specified
564 functions are called. In its simplest form:
565
566        (TRACE NAME-1 NAME-2 ...)
567
568 The NAMEs are not evaluated. Each may be a symbol, denoting an
569 individual function, or a string, denoting all functions fbound to
570 symbols whose home package is the package with the given name.
571
572 Options allow modification of the default behavior. Each option is a
573 pair of an option keyword and a value form. Global options are
574 specified before the first name, and affect all functions traced by a
575 given use of TRACE. Options may also be interspersed with function
576 names, in which case they act as local options, only affecting tracing
577 of the immediately preceding function name. Local options override
578 global options.
579
580 By default, TRACE causes a printout on *TRACE-OUTPUT* each time that
581 one of the named functions is entered or returns. (This is the basic,
582 ANSI Common Lisp behavior of TRACE.) As an SBCL extension, the
583 :REPORT SB-EXT:PROFILE option can be used to instead cause information
584 to be silently recorded to be inspected later using the SB-EXT:PROFILE
585 function.
586
587 The following options are defined:
588
589    :REPORT Report-Type
590        If Report-Type is TRACE (the default) then information is reported
591        by printing immediately. If Report-Type is SB-EXT:PROFILE, information
592        is recorded for later summary by calls to SB-EXT:PROFILE. If
593        Report-Type is NIL, then the only effect of the trace is to execute
594        other options (e.g. PRINT or BREAK).
595
596    :CONDITION Form
597    :CONDITION-AFTER Form
598    :CONDITION-ALL Form
599        If :CONDITION is specified, then TRACE does nothing unless Form
600        evaluates to true at the time of the call. :CONDITION-AFTER is
601        similar, but suppresses the initial printout, and is tested when the
602        function returns. :CONDITION-ALL tries both before and after.
603        This option is not supported with :REPORT PROFILE.
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\". This option is not
625        supported with :REPORT PROFILE.
626
627    :ENCAPSULATE {:DEFAULT | T | NIL}
628        If T, the tracing is done via encapsulation (redefining the function
629        name) rather than by modifying the function. :DEFAULT is the default,
630        and means to use encapsulation for interpreted functions and funcallable
631        instances, breakpoints otherwise. When encapsulation is used, forms are
632        *not* evaluated in the function's lexical environment, but SB-DEBUG:ARG
633        can still be used.
634
635    :METHODS {T | NIL}
636        If T, any function argument naming a generic function will have its
637        methods traced in addition to the generic function itself.
638
639    :FUNCTION Function-Form
640        This is a not really an option, but rather another way of specifying
641        what function to trace. The Function-Form is evaluated immediately,
642        and the resulting function is instrumented, i.e. traced or profiled
643        as specified in REPORT.
644
645 :CONDITION, :BREAK and :PRINT forms are evaluated in a context which
646 mocks up the lexical environment of the called function, so that
647 SB-DEBUG:VAR and SB-DEBUG:ARG can be used. The -AFTER and -ALL forms
648 are evaluated in the null environment."
649   (if specs
650       (expand-trace specs)
651       '(%list-traced-funs)))
652 \f
653 ;;;; untracing
654
655 ;;; Untrace one function.
656 (defun untrace-1 (function-or-name)
657   (let* ((fun (trace-fdefinition function-or-name))
658          (info (when fun (gethash fun *traced-funs*))))
659     (cond
660       ((and fun (not info))
661        (warn "Function is not TRACEd: ~S" function-or-name))
662       ((not fun)
663        ;; Someone has FMAKUNBOUND it.
664        (let ((table *traced-funs*))
665          (with-locked-system-table (table)
666            (maphash (lambda (fun info)
667                       (when (equal function-or-name (trace-info-what info))
668                         (remhash fun table)))
669                     table))))
670       (t
671        (cond
672          ((trace-info-encapsulated info)
673           (unencapsulate (trace-info-what info) 'trace))
674          (t
675           (sb-di:delete-breakpoint (trace-info-start-breakpoint info))
676           (sb-di:delete-breakpoint (trace-info-end-breakpoint info))))
677        (setf (trace-info-untraced info) t)
678        (remhash fun *traced-funs*)))))
679
680 ;;; Untrace all traced functions.
681 (defun untrace-all ()
682   (dolist (fun (%list-traced-funs))
683     (untrace-1 fun))
684   t)
685
686 (defun untrace-package (name)
687   (let ((package (find-package name)))
688     (when package
689       (dolist (fun (%list-traced-funs))
690         (cond ((and (symbolp fun) (eq package (symbol-package fun)))
691                (untrace-1 fun))
692               ((and (consp fun) (eq 'setf (car fun))
693                     (symbolp (second fun))
694                     (eq package (symbol-package (second fun))))
695                (untrace-1 fun)))))))
696
697 (defmacro untrace (&rest specs)
698   #+sb-doc
699   "Remove tracing from the specified functions. Untraces all
700 functions when called with no arguments."
701   (if specs
702       `(progn
703          ,@(loop while specs
704                  for name = (pop specs)
705                  collect (cond ((eq name :function)
706                                 `(untrace-1 ,(pop specs)))
707                                ((stringp name)
708                                 `(untrace-package ,name))
709                                (t
710                                 `(untrace-1 ',name))))
711          t)
712       '(untrace-all)))