b52c1de18e2f68f760e23b040eb8b526e759c75e
[sbcl.git] / src / code / ntrace.lisp
1 ;;;; a tracing facility based on breakpoints
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* :default
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-functions* (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 (function-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 ;;; :FUNCTION-END breakpoint used for TRACE'ing, we look for the
95 ;;; FUNCTION-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     (if (or #+sb-interpreter (sb-eval:interpreted-function-p res)
129             nil)
130         (values res
131                 named-p
132                 #+sb-interpreter (if (sb-eval:interpreted-function-closure res)
133                                      :interpreted-closure :interpreted))
134         (case (sb-kernel:get-type res)
135           (#.sb-vm:closure-header-type
136            (values (sb-kernel:%closure-function res)
137                    named-p
138                    :compiled-closure))
139           (#.sb-vm:funcallable-instance-header-type
140            (values res named-p :funcallable-instance))
141           (t (values res named-p :compiled))))))
142
143 ;;; When a function name is redefined, and we were tracing that name,
144 ;;; then untrace the old definition and trace the new one.
145 (defun trace-redefined-update (fname new-value)
146   (when (fboundp fname)
147     (let* ((fun (trace-fdefinition fname))
148            (info (gethash fun *traced-functions*)))
149       (when (and info (trace-info-named info))
150         (untrace-1 fname)
151         (trace-1 fname info new-value)))))
152 (push #'trace-redefined-update *setf-fdefinition-hook*)
153
154 ;;; Annotate some forms to evaluate with pre-converted functions. Each
155 ;;; form is really a cons (exp . function). Loc is the code location
156 ;;; to use for the lexical environment. If Loc is NIL, evaluate in the
157 ;;; null environment. If Form is NIL, just return NIL.
158 (defun coerce-form (form loc)
159   (when form
160     (let ((exp (car form)))
161       (if (sb-di:code-location-p loc)
162           (let ((fun (sb-di:preprocess-for-eval exp loc)))
163             (cons exp
164                   #'(lambda (frame)
165                       (let ((*current-frame* frame))
166                         (funcall fun frame)))))
167           (let* ((bod (ecase loc
168                         ((nil) exp)
169                         (:encapsulated
170                          `(flet ((sb-debug:arg (n)
171                                    (declare (special argument-list))
172                                    (elt argument-list n)))
173                             (declare (ignorable #'sb-debug:arg))
174                             ,exp))))
175                  (fun (coerce `(lambda () ,bod) 'function)))
176             (cons exp
177                   #'(lambda (frame)
178                       (declare (ignore frame))
179                       (let ((*current-frame* nil))
180                         (funcall fun)))))))))
181 (defun coerce-form-list (forms loc)
182   (mapcar #'(lambda (x) (coerce-form x loc)) forms))
183
184 ;;; Print indentation according to the number of trace entries.
185 ;;; Entries whose condition was false don't count.
186 (defun print-trace-indentation ()
187   (let ((depth 0))
188     (dolist (entry *traced-entries*)
189       (when (cdr entry) (incf depth)))
190     (format t
191             "~@V,0T~D: "
192             (+ (mod (* depth *trace-indentation-step*)
193                     (- *max-trace-indentation* *trace-indentation-step*))
194                *trace-indentation-step*)
195             depth)))
196
197 ;;; Return true if one of the Names appears on the stack below Frame.
198 (defun trace-wherein-p (frame names)
199   (do ((frame (sb-di:frame-down frame) (sb-di:frame-down frame)))
200       ((not frame) nil)
201     (when (member (sb-di:debug-function-name (sb-di:frame-debug-function
202                                               frame))
203                   names
204                   :test #'equal)
205       (return t))))
206
207 ;;; Handle print and print-after options.
208 (defun trace-print (frame forms)
209   (dolist (ele forms)
210     (fresh-line)
211     (print-trace-indentation)
212     (format t "~S = ~S" (car ele) (funcall (cdr ele) frame))))
213
214 ;;; Test a break option, and break if true.
215 (defun trace-maybe-break (info break where frame)
216   (when (and break (funcall (cdr break) frame))
217     (sb-di:flush-frames-above frame)
218     (let ((*stack-top-hint* frame))
219       (break "breaking ~A traced call to ~S:"
220              where
221              (trace-info-what info)))))
222
223 ;;; This function discards any invalid cookies on our simulated stack.
224 ;;; Encapsulated entries are always valid, since we bind
225 ;;; *TRACED-ENTRIES* in the encapsulation.
226 (defun discard-invalid-entries (frame)
227   (loop
228     (when (or (null *traced-entries*)
229               (let ((cookie (caar *traced-entries*)))
230                 (or (not cookie)
231                     (sb-di:function-end-cookie-valid-p frame cookie))))
232       (return))
233     (pop *traced-entries*)))
234 \f
235 ;;;; hook functions
236
237 ;;; Return a closure that can be used for a function start breakpoint
238 ;;; hook function and a closure that can be used as the
239 ;;; FUNCTION-END-COOKIE function. The first communicates the sense of
240 ;;; the Condition to the second via a closure variable.
241 (defun trace-start-breakpoint-fun (info)
242   (let (conditionp)
243     (values
244      #'(lambda (frame bpt)
245          (declare (ignore bpt))
246          (discard-invalid-entries frame)
247          (let ((condition (trace-info-condition info))
248                (wherein (trace-info-wherein info)))
249            (setq conditionp
250                  (and (not *in-trace*)
251                       (or (not condition)
252                           (funcall (cdr condition) frame))
253                       (or (not wherein)
254                           (trace-wherein-p frame wherein)))))
255
256          (when conditionp
257            (let ((sb-kernel:*current-level* 0)
258                  (*standard-output* *trace-output*)
259                  (*in-trace* t))
260              (fresh-line)
261              (print-trace-indentation)
262              (if (trace-info-encapsulated info)
263                  (locally (declare (special basic-definition argument-list))
264                    (prin1 `(,(trace-info-what info) ,@argument-list)))
265                  (print-frame-call frame))
266              (terpri)
267              (trace-print frame (trace-info-print info)))
268            (trace-maybe-break info (trace-info-break info) "before" frame)))
269
270      #'(lambda (frame cookie)
271          (declare (ignore frame))
272          (push (cons cookie conditionp) *traced-entries*)))))
273
274 ;;; This prints a representation of the return values delivered.
275 ;;; First, this checks to see that cookie is at the top of
276 ;;; *TRACED-ENTRIES*; if it is not, then we need to adjust this list
277 ;;; to determine the correct indentation for output. We then check to
278 ;;; see whether the function is still traced and that the condition
279 ;;; succeeded before printing anything.
280 (defun trace-end-breakpoint-fun (info)
281   #'(lambda (frame bpt *trace-values* cookie)
282       (declare (ignore bpt))
283       (unless (eq cookie (caar *traced-entries*))
284         (setf *traced-entries*
285               (member cookie *traced-entries* :key #'car)))
286
287       (let ((entry (pop *traced-entries*)))
288         (when (and (not (trace-info-untraced info))
289                    (or (cdr entry)
290                        (let ((cond (trace-info-condition-after info)))
291                          (and cond (funcall (cdr cond) frame)))))
292           (let ((sb-kernel:*current-level* 0)
293                 (*standard-output* *trace-output*)
294                 (*in-trace* t))
295             (fresh-line)
296             (pprint-logical-block (*standard-output* nil)
297               (print-trace-indentation)
298               (pprint-indent :current 2)
299               (format t "~S returned" (trace-info-what info))
300               (dolist (v *trace-values*)
301                 (write-char #\space)
302                 (pprint-newline :linear)
303                 (prin1 v)))
304             (terpri)
305             (trace-print frame (trace-info-print-after info)))
306           (trace-maybe-break info
307                              (trace-info-break-after info)
308                              "after"
309                              frame)))))
310 \f
311 ;;; This function is called by the trace encapsulation. It calls the
312 ;;; breakpoint hook functions with NIL for the breakpoint and cookie, which
313 ;;; we have cleverly contrived to work for our hook functions.
314 (defun trace-call (info)
315   (multiple-value-bind (start cookie) (trace-start-breakpoint-fun info)
316     (let ((frame (sb-di:frame-down (sb-di:top-frame))))
317       (funcall start frame nil)
318       (let ((*traced-entries* *traced-entries*))
319         (declare (special basic-definition argument-list))
320         (funcall cookie frame nil)
321         (let ((vals
322                (multiple-value-list
323                 (apply basic-definition argument-list))))
324           (funcall (trace-end-breakpoint-fun info) frame nil vals nil)
325           (values-list vals))))))
326 \f
327 ;;; Trace one function according to the specified options. We copy the
328 ;;; trace info (it was a quoted constant), fill in the functions, and
329 ;;; then install the breakpoints or encapsulation.
330 ;;;
331 ;;; If non-null, DEFINITION is the new definition of a function that
332 ;;; we are automatically retracing.
333 (defun trace-1 (function-or-name info &optional definition)
334   (multiple-value-bind (fun named kind)
335       (if definition
336           (values definition t
337                   (nth-value 2 (trace-fdefinition definition)))
338           (trace-fdefinition function-or-name))
339     (when (gethash fun *traced-functions*)
340       (warn "~S is already TRACE'd, untracing it." function-or-name)
341       (untrace-1 fun))
342
343     (let* ((debug-fun (sb-di:function-debug-function fun))
344            (encapsulated
345             (if (eq (trace-info-encapsulated info) :default)
346                 (ecase kind
347                   (:compiled nil)
348                   (:compiled-closure
349                    (unless (functionp function-or-name)
350                      (warn "Tracing shared code for ~S:~%  ~S"
351                            function-or-name
352                            fun))
353                    nil)
354                   ((:interpreted :interpreted-closure :funcallable-instance)
355                    t))
356                 (trace-info-encapsulated info)))
357            (loc (if encapsulated
358                     :encapsulated
359                     (sb-di:debug-function-start-location debug-fun)))
360            (info (make-trace-info
361                   :what function-or-name
362                   :named named
363                   :encapsulated encapsulated
364                   :wherein (trace-info-wherein info)
365                   :condition (coerce-form (trace-info-condition info) loc)
366                   :break (coerce-form (trace-info-break info) loc)
367                   :print (coerce-form-list (trace-info-print info) loc)
368                   :break-after (coerce-form (trace-info-break-after info) nil)
369                   :condition-after
370                   (coerce-form (trace-info-condition-after info) nil)
371                   :print-after
372                   (coerce-form-list (trace-info-print-after info) nil))))
373
374       (dolist (wherein (trace-info-wherein info))
375         (unless (or (stringp wherein)
376                     (fboundp wherein))
377           (warn ":WHEREIN name ~S is not a defined global function."
378                 wherein)))
379
380       (cond
381        (encapsulated
382         (unless named
383           (error "can't use encapsulation to trace anonymous function ~S"
384                  fun))
385         (encapsulate function-or-name 'trace `(trace-call ',info)))
386        (t
387         (multiple-value-bind (start-fun cookie-fun)
388             (trace-start-breakpoint-fun info)
389           (let ((start (sb-di:make-breakpoint start-fun debug-fun
390                                               :kind :function-start))
391                 (end (sb-di:make-breakpoint
392                       (trace-end-breakpoint-fun info)
393                       debug-fun :kind :function-end
394                       :function-end-cookie cookie-fun)))
395             (setf (trace-info-start-breakpoint info) start)
396             (setf (trace-info-end-breakpoint info) end)
397             ;; The next two forms must be in the order in which they
398             ;; appear, since the start breakpoint must run before the
399             ;; function-end breakpoint's start helper (which calls the
400             ;; cookie function.) One reason is that cookie function
401             ;; requires that the CONDITIONP shared closure variable be
402             ;; initialized.
403             (sb-di:activate-breakpoint start)
404             (sb-di:activate-breakpoint end)))))
405
406       (setf (gethash fun *traced-functions*) info)))
407
408   function-or-name)
409 \f
410 ;;;; the TRACE macro
411
412 ;;; Parse leading trace options off of SPECS, modifying INFO
413 ;;; accordingly. The remaining portion of the list is returned when we
414 ;;; encounter a plausible function name.
415 (defun parse-trace-options (specs info)
416   (let ((current specs))
417     (loop
418       (when (endp current) (return))
419       (let ((option (first current))
420             (value (cons (second current) nil)))
421         (case option
422           (:report (error "stub: The :REPORT option is not yet implemented."))
423           (:condition (setf (trace-info-condition info) value))
424           (:condition-after
425            (setf (trace-info-condition info) (cons nil nil))
426            (setf (trace-info-condition-after info) value))
427           (:condition-all
428            (setf (trace-info-condition info) value)
429            (setf (trace-info-condition-after info) value))
430           (:wherein
431            (setf (trace-info-wherein info)
432                  (if (listp (car value)) (car value) value)))
433           (:encapsulate
434            (setf (trace-info-encapsulated info) (car value)))
435           (:break (setf (trace-info-break info) value))
436           (:break-after (setf (trace-info-break-after info) value))
437           (:break-all
438            (setf (trace-info-break info) value)
439            (setf (trace-info-break-after info) value))
440           (:print
441            (setf (trace-info-print info)
442                  (append (trace-info-print info) (list value))))
443           (:print-after
444            (setf (trace-info-print-after info)
445                  (append (trace-info-print-after info) (list value))))
446           (:print-all
447            (setf (trace-info-print info)
448                  (append (trace-info-print info) (list value)))
449            (setf (trace-info-print-after info)
450                  (append (trace-info-print-after info) (list value))))
451           (t (return)))
452         (pop current)
453         (unless current
454           (error "missing argument to ~S TRACE option" option))
455         (pop current)))
456     current))
457
458 ;;; Compute the expansion of TRACE in the non-trivial case (arguments
459 ;;; specified.) If there are no :FUNCTION specs, then don't use a LET.
460 ;;; This allows TRACE to be used without the full interpreter.
461 (defun expand-trace (specs)
462   (collect ((binds)
463             (forms))
464     (let* ((global-options (make-trace-info))
465            (current (parse-trace-options specs global-options)))
466       (loop
467         (when (endp current) (return))
468         (let ((name (pop current))
469               (options (copy-trace-info global-options)))
470           (cond
471            ((eq name :function)
472             (let ((temp (gensym)))
473               (binds `(,temp ,(pop current)))
474               (forms `(trace-1 ,temp ',options))))
475            ((and (keywordp name)
476                  (not (or (fboundp name) (macro-function name))))
477             (error "unknown TRACE option: ~S" name))
478            (t
479             (forms `(trace-1 ',name ',options))))
480           (setq current (parse-trace-options current options)))))
481
482     (if (binds)
483         `(let ,(binds) (list ,@(forms)))
484         `(list ,@(forms)))))
485
486 (defun %list-traced-functions ()
487   (loop for x being each hash-value in *traced-functions*
488         collect (trace-info-what x)))
489
490 (defmacro trace (&rest specs)
491   #+sb-doc
492   "TRACE {Option Global-Value}* {Name {Option Value}*}*
493    TRACE is a debugging tool that provides information when specified functions
494    are called. In its simplest form:
495        (trace Name-1 Name-2 ...)
496    (The Names are not evaluated.)
497
498    Options allow modification of the default behavior. Each option is a pair
499    of an option keyword and a value form. Global options are specified before
500    the first name, and affect all functions traced by a given use of TRACE.
501    Options may also be interspersed with function names, in which case they
502    act as local options, only affecting tracing of the immediately preceding
503    function name. Local options override global options.
504
505    By default, TRACE causes a printout on *TRACE-OUTPUT* each time that
506    one of the named functions is entered or returns. (This is the
507    basic, ANSI Common Lisp behavior of TRACE.) As an SBCL extension, the
508    :REPORT SB-EXT:PROFILE option can be used to instead cause information
509    to be silently recorded to be inspected later using the SB-EXT:PROFILE
510    function.
511
512    The following options are defined:
513
514    :REPORT Report-Type
515        If Report-Type is TRACE (the default) then information is reported
516        by printing immediately. If Report-Type is SB-EXT:PROFILE, information
517        is recorded for later summary by calls to SB-EXT:PROFILE. If
518        Report-Type is NIL, then the only effect of the trace is to execute
519        other options (e.g. PRINT or BREAK).
520
521    :CONDITION Form
522    :CONDITION-AFTER Form
523    :CONDITION-ALL Form
524        If :CONDITION is specified, then TRACE does nothing unless Form
525        evaluates to true at the time of the call. :CONDITION-AFTER is
526        similar, but suppresses the initial printout, and is tested when the
527        function returns. :CONDITION-ALL tries both before and after.
528
529    :BREAK Form
530    :BREAK-AFTER Form
531    :BREAK-ALL Form
532        If specified, and Form evaluates to true, then the debugger is invoked
533        at the start of the function, at the end of the function, or both,
534        according to the respective option. 
535
536    :PRINT Form
537    :PRINT-AFTER Form
538    :PRINT-ALL Form
539        In addition to the usual printout, the result of evaluating Form is
540        printed at the start of the function, at the end of the function, or
541        both, according to the respective option. Multiple print options cause
542        multiple values to be printed.
543
544    :WHEREIN Names
545        If specified, Names is a function name or list of names. TRACE does
546        nothing unless a call to one of those functions encloses the call to
547        this function (i.e. it would appear in a backtrace.)  Anonymous
548        functions have string names like \"DEFUN FOO\". 
549
550    :ENCAPSULATE {:DEFAULT | T | NIL}
551        If T, the tracing is done via encapsulation (redefining the function
552        name) rather than by modifying the function. :DEFAULT is the default,
553        and means to use encapsulation for interpreted functions and funcallable
554        instances, breakpoints otherwise. When encapsulation is used, forms are
555        *not* evaluated in the function's lexical environment, but SB-DEBUG:ARG
556        can still be used.
557
558    :FUNCTION Function-Form
559        This is a not really an option, but rather another way of specifying
560        what function to trace. The Function-Form is evaluated immediately,
561        and the resulting function is traced.
562
563    :CONDITION, :BREAK and :PRINT forms are evaluated in the lexical environment
564    of the called function; SB-DEBUG:VAR and SB-DEBUG:ARG can be used. The
565    -AFTER and -ALL forms are evaluated in the null environment."
566   (if specs
567       (expand-trace specs)
568       '(%list-traced-functions)))
569 \f
570 ;;;; untracing
571
572 ;;; Untrace one function.
573 (defun untrace-1 (function-or-name)
574   (let* ((fun (trace-fdefinition function-or-name))
575          (info (gethash fun *traced-functions*)))
576     (cond
577      ((not info)
578       (warn "Function is not TRACEd: ~S" function-or-name))
579      (t
580       (cond
581        ((trace-info-encapsulated info)
582         (unencapsulate (trace-info-what info) 'trace))
583        (t
584         (sb-di:delete-breakpoint (trace-info-start-breakpoint info))
585         (sb-di:delete-breakpoint (trace-info-end-breakpoint info))))
586       (setf (trace-info-untraced info) t)
587       (remhash fun *traced-functions*)))))
588
589 ;;; Untrace all traced functions.
590 (defun untrace-all ()
591   (dolist (fun (%list-traced-functions))
592     (untrace-1 fun))
593   t)
594
595 (defmacro untrace (&rest specs)
596   #+sb-doc
597   "Remove tracing from the specified functions. With no args, untrace all
598    functions."
599   (if specs
600       (collect ((res))
601         (let ((current specs))
602           (loop
603             (unless current (return))
604             (let ((name (pop current)))
605               (res (if (eq name :function)
606                        `(untrace-1 ,(pop current))
607                        `(untrace-1 ',name)))))
608           `(progn ,@(res) t)))
609       '(untrace-all)))