0.8.14.20: Documentation madness, yet again
[sbcl.git] / src / code / ntrace.lisp
index e775902..c5c80b6 100644 (file)
@@ -1,4 +1,4 @@
-;;;; a tracing facility based on breakpoints
+;;;; a tracing facility
 
 ;;;; This software is part of the SBCL system. See the README file for
 ;;;; more information.
   "If the trace indentation exceeds this value, then indentation restarts at
    0.")
 
-(defvar *trace-encapsulate-default* :default
+(defvar *trace-encapsulate-default* t
   #+sb-doc
   "the default value for the :ENCAPSULATE option to TRACE")
 \f
 ;;;; internal state
 
 ;;; a hash table that maps each traced function to the TRACE-INFO. The
-;;; entry for a closure is the shared function-entry object.
-(defvar *traced-functions* (make-hash-table :test 'eq))
+;;; entry for a closure is the shared function entry object.
+(defvar *traced-funs* (make-hash-table :test 'eq))
 
 ;;; A TRACE-INFO object represents all the information we need to
 ;;; trace a given function.
@@ -81,7 +81,7 @@
   ;; list of null environment forms
   (print-after () :type list))
 
-;;; This is a list of conses (function-end-cookie . condition-satisfied),
+;;; This is a list of conses (fun-end-cookie . condition-satisfied),
 ;;; which we use to note distinct dynamic entries into functions. When
 ;;; we enter a traced function, we add a entry to this list holding
 ;;; the new end-cookie and whether the trace condition was satisfied.
@@ -91,8 +91,8 @@
 ;;;
 ;;; This list also helps us synchronize the TRACE facility dynamically
 ;;; for detecting non-local flow of control. Whenever execution hits a
-;;; :FUNCTION-END breakpoint used for TRACE'ing, we look for the
-;;; FUNCTION-END-COOKIE at the top of *TRACED-ENTRIES*. If it is not
+;;; :FUN-END breakpoint used for TRACE'ing, we look for the
+;;; FUN-END-COOKIE at the top of *TRACED-ENTRIES*. If it is not
 ;;; there, we discard any entries that come before our cookie.
 ;;;
 ;;; When we trace using encapsulation, we bind this variable and add
                (values (fdefinition x) t))))
        (function x)
        (t (values (fdefinition x) t)))
-    (case (sb-kernel:get-type res)
-      (#.sb-vm:closure-header-type
-       (values (sb-kernel:%closure-function res)
+    (case (sb-kernel:widetag-of res)
+      (#.sb-vm:closure-header-widetag
+       (values (sb-kernel:%closure-fun res)
               named-p
               :compiled-closure))
-      (#.sb-vm:funcallable-instance-header-type
+      (#.sb-vm:funcallable-instance-header-widetag
        (values res named-p :funcallable-instance))
       (t (values res named-p :compiled)))))
 
 (defun trace-redefined-update (fname new-value)
   (when (fboundp fname)
     (let* ((fun (trace-fdefinition fname))
-          (info (gethash fun *traced-functions*)))
+          (info (gethash fun *traced-funs*)))
       (when (and info (trace-info-named info))
        (untrace-1 fname)
        (trace-1 fname info new-value)))))
 (push #'trace-redefined-update *setf-fdefinition-hook*)
 
-;;; Annotate some forms to evaluate with pre-converted functions. Each
-;;; form is really a cons (exp . function). Loc is the code location
-;;; to use for the lexical environment. If Loc is NIL, evaluate in the
-;;; null environment. If Form is NIL, just return NIL.
+;;; Annotate a FORM to evaluate with pre-converted functions. FORM is
+;;; really a cons (EXP . FUNCTION). LOC is the code location to use
+;;; for the lexical environment. If LOC is NIL, evaluate in the null
+;;; environment. If FORM is NIL, just return NIL.
 (defun coerce-form (form loc)
   (when form
     (let ((exp (car form)))
       (if (sb-di:code-location-p loc)
          (let ((fun (sb-di:preprocess-for-eval exp loc)))
+            (declare (type function fun))
            (cons exp
-                 #'(lambda (frame)
-                     (let ((*current-frame* frame))
-                       (funcall fun frame)))))
+                 (lambda (frame)
+                   (let ((*current-frame* frame))
+                     (funcall fun frame)))))
          (let* ((bod (ecase loc
                        ((nil) exp)
                        (:encapsulated
-                        `(flet ((sb-debug:arg (n)
-                                  (declare (special argument-list))
-                                  (elt argument-list n)))
-                           (declare (ignorable #'sb-debug:arg))
-                           ,exp))))
+                        `(locally (declare (disable-package-locks sb-debug:arg arg-list))
+                           (flet ((sb-debug:arg (n)
+                                    (declare (special arg-list))
+                                    (elt arg-list n)))
+                             (declare (ignorable #'sb-debug:arg)
+                                      (enable-package-locks sb-debug:arg arg-list))
+                             ,exp)))))
                 (fun (coerce `(lambda () ,bod) 'function)))
            (cons exp
-                 #'(lambda (frame)
-                     (declare (ignore frame))
-                     (let ((*current-frame* nil))
-                       (funcall fun)))))))))
+                 (lambda (frame)
+                   (declare (ignore frame))
+                   (let ((*current-frame* nil))
+                     (funcall fun)))))))))
+
 (defun coerce-form-list (forms loc)
-  (mapcar #'(lambda (x) (coerce-form x loc)) forms))
+  (mapcar (lambda (x) (coerce-form x loc)) forms))
 
 ;;; Print indentation according to the number of trace entries.
 ;;; Entries whose condition was false don't count.
     (dolist (entry *traced-entries*)
       (when (cdr entry) (incf depth)))
     (format t
-           "~@V,0T~D: "
+           "~V,0@T~W: "
            (+ (mod (* depth *trace-indentation-step*)
                    (- *max-trace-indentation* *trace-indentation-step*))
               *trace-indentation-step*)
            depth)))
 
-;;; Return true if one of the Names appears on the stack below Frame.
+;;; Return true if any of the NAMES appears on the stack below FRAME.
 (defun trace-wherein-p (frame names)
   (do ((frame (sb-di:frame-down frame) (sb-di:frame-down frame)))
       ((not frame) nil)
                  :test #'equal)
       (return t))))
 
-;;; Handle print and print-after options.
+;;; Handle PRINT and PRINT-AFTER options.
 (defun trace-print (frame forms)
   (dolist (ele forms)
     (fresh-line)
     (print-trace-indentation)
-    (format t "~S = ~S" (car ele) (funcall (cdr ele) frame))))
+    (format t "~@<~S ~_= ~S~:>" (car ele) (funcall (cdr ele) frame))
+    (terpri)))
 
-;;; Test a break option, and break if true.
+;;; Test a BREAK option, and if true, break.
 (defun trace-maybe-break (info break where frame)
   (when (and break (funcall (cdr break) frame))
     (sb-di:flush-frames-above frame)
             where
             (trace-info-what info)))))
 
-;;; This function discards any invalid cookies on our simulated stack.
-;;; Encapsulated entries are always valid, since we bind
-;;; *TRACED-ENTRIES* in the encapsulation.
+;;; Discard any invalid cookies on our simulated stack. Encapsulated
+;;; entries are always valid, since we bind *TRACED-ENTRIES* in the
+;;; encapsulation.
 (defun discard-invalid-entries (frame)
   (loop
     (when (or (null *traced-entries*)
              (let ((cookie (caar *traced-entries*)))
                (or (not cookie)
-                   (sb-di:function-end-cookie-valid-p frame cookie))))
+                   (sb-di:fun-end-cookie-valid-p frame cookie))))
       (return))
     (pop *traced-entries*)))
 \f
 ;;;; hook functions
 
 ;;; Return a closure that can be used for a function start breakpoint
-;;; hook function and a closure that can be used as the
-;;; FUNCTION-END-COOKIE function. The first communicates the sense of
-;;; the Condition to the second via a closure variable.
+;;; hook function and a closure that can be used as the FUN-END-COOKIE
+;;; function. The first communicates the sense of the
+;;; TRACE-INFO-CONDITION to the second via a closure variable.
 (defun trace-start-breakpoint-fun (info)
   (let (conditionp)
     (values
-     #'(lambda (frame bpt)
-        (declare (ignore bpt))
-        (discard-invalid-entries frame)
-        (let ((condition (trace-info-condition info))
-              (wherein (trace-info-wherein info)))
-          (setq conditionp
-                (and (not *in-trace*)
-                     (or (not condition)
-                         (funcall (cdr condition) frame))
-                     (or (not wherein)
-                         (trace-wherein-p frame wherein)))))
-
-        (when conditionp
-          (let ((sb-kernel:*current-level* 0)
-                (*standard-output* *trace-output*)
-                (*in-trace* t))
-            (fresh-line)
-            (print-trace-indentation)
-            (if (trace-info-encapsulated info)
-                (locally (declare (special basic-definition argument-list))
-                  (prin1 `(,(trace-info-what info) ,@argument-list)))
-                (print-frame-call frame))
-            (terpri)
-            (trace-print frame (trace-info-print info)))
-          (trace-maybe-break info (trace-info-break info) "before" frame)))
-
-     #'(lambda (frame cookie)
-        (declare (ignore frame))
-        (push (cons cookie conditionp) *traced-entries*)))))
+
+     (lambda (frame bpt)
+       (declare (ignore bpt))
+       (discard-invalid-entries frame)
+       (let ((condition (trace-info-condition info))
+            (wherein (trace-info-wherein info)))
+        (setq conditionp
+              (and (not *in-trace*)
+                   (or (not condition)
+                       (funcall (cdr condition) frame))
+                   (or (not wherein)
+                       (trace-wherein-p frame wherein)))))
+       (when conditionp
+        (let ((sb-kernel:*current-level-in-print* 0)
+              (*standard-output* (make-string-output-stream))
+              (*in-trace* t))
+          (fresh-line)
+          (print-trace-indentation)
+          (if (trace-info-encapsulated info)
+              ;; FIXME: These special variables should be given
+              ;; *FOO*-style names, and probably declared globally
+              ;; with DEFVAR.
+              (locally
+                (declare (special basic-definition arg-list))
+                (prin1 `(,(trace-info-what info) ,@arg-list)))
+              (print-frame-call frame))
+          (terpri)
+          (trace-print frame (trace-info-print info))
+          (write-sequence (get-output-stream-string *standard-output*)
+                          *trace-output*))
+        (trace-maybe-break info (trace-info-break info) "before" frame)))
+
+     (lambda (frame cookie)
+       (declare (ignore frame))
+       (push (cons cookie conditionp) *traced-entries*)))))
 
 ;;; This prints a representation of the return values delivered.
 ;;; First, this checks to see that cookie is at the top of
 ;;; to determine the correct indentation for output. We then check to
 ;;; see whether the function is still traced and that the condition
 ;;; succeeded before printing anything.
+(declaim (ftype (function (trace-info) function) trace-end-breakpoint-fun))
 (defun trace-end-breakpoint-fun (info)
-  #'(lambda (frame bpt *trace-values* cookie)
-      (declare (ignore bpt))
-      (unless (eq cookie (caar *traced-entries*))
-       (setf *traced-entries*
-             (member cookie *traced-entries* :key #'car)))
-
-      (let ((entry (pop *traced-entries*)))
-       (when (and (not (trace-info-untraced info))
-                  (or (cdr entry)
-                      (let ((cond (trace-info-condition-after info)))
-                        (and cond (funcall (cdr cond) frame)))))
-         (let ((sb-kernel:*current-level* 0)
-               (*standard-output* *trace-output*)
-               (*in-trace* t))
-           (fresh-line)
-           (pprint-logical-block (*standard-output* nil)
-             (print-trace-indentation)
-             (pprint-indent :current 2)
-             (format t "~S returned" (trace-info-what info))
-             (dolist (v *trace-values*)
-               (write-char #\space)
-               (pprint-newline :linear)
-               (prin1 v)))
-           (terpri)
-           (trace-print frame (trace-info-print-after info)))
-         (trace-maybe-break info
-                            (trace-info-break-after info)
-                            "after"
-                            frame)))))
+  (lambda (frame bpt *trace-values* cookie)
+    (declare (ignore bpt))
+    (unless (eq cookie (caar *traced-entries*))
+      (setf *traced-entries*
+           (member cookie *traced-entries* :key #'car)))
+
+    (let ((entry (pop *traced-entries*)))
+      (when (and (not (trace-info-untraced info))
+                (or (cdr entry)
+                    (let ((cond (trace-info-condition-after info)))
+                      (and cond (funcall (cdr cond) frame)))))
+       (let ((sb-kernel:*current-level-in-print* 0)
+             (*standard-output* (make-string-output-stream))
+             (*in-trace* t))
+         (fresh-line)
+         (pprint-logical-block (*standard-output* nil)
+           (print-trace-indentation)
+           (pprint-indent :current 2)
+           (format t "~S returned" (trace-info-what info))
+           (dolist (v *trace-values*)
+             (write-char #\space)
+             (pprint-newline :linear)
+             (prin1 v)))
+         (terpri)
+         (trace-print frame (trace-info-print-after info))
+         (write-sequence (get-output-stream-string *standard-output*)
+                         *trace-output*))
+       (trace-maybe-break info
+                          (trace-info-break-after info)
+                          "after"
+                          frame)))))
 \f
 ;;; This function is called by the trace encapsulation. It calls the
-;;; breakpoint hook functions with NIL for the breakpoint and cookie, which
-;;; we have cleverly contrived to work for our hook functions.
+;;; breakpoint hook functions with NIL for the breakpoint and cookie,
+;;; which we have cleverly contrived to work for our hook functions.
 (defun trace-call (info)
   (multiple-value-bind (start cookie) (trace-start-breakpoint-fun info)
+    (declare (type function start cookie))
     (let ((frame (sb-di:frame-down (sb-di:top-frame))))
       (funcall start frame nil)
       (let ((*traced-entries* *traced-entries*))
-       (declare (special basic-definition argument-list))
+       (declare (special basic-definition arg-list))
        (funcall cookie frame nil)
        (let ((vals
               (multiple-value-list
-               (apply basic-definition argument-list))))
+               (apply basic-definition arg-list))))
          (funcall (trace-end-breakpoint-fun info) frame nil vals nil)
          (values-list vals))))))
 \f
          (values definition t
                  (nth-value 2 (trace-fdefinition definition)))
          (trace-fdefinition function-or-name))
-    (when (gethash fun *traced-functions*)
-      (warn "~S is already TRACE'd, untracing it." function-or-name)
+    (when (gethash fun *traced-funs*)
+      (warn "~S is already TRACE'd, untracing it first." function-or-name)
       (untrace-1 fun))
 
     (let* ((debug-fun (sb-di:fun-debug-fun fun))
        (multiple-value-bind (start-fun cookie-fun)
            (trace-start-breakpoint-fun info)
          (let ((start (sb-di:make-breakpoint start-fun debug-fun
-                                             :kind :function-start))
+                                             :kind :fun-start))
                (end (sb-di:make-breakpoint
                      (trace-end-breakpoint-fun info)
-                     debug-fun :kind :function-end
-                     :function-end-cookie cookie-fun)))
+                     debug-fun :kind :fun-end
+                     :fun-end-cookie cookie-fun)))
            (setf (trace-info-start-breakpoint info) start)
            (setf (trace-info-end-breakpoint info) end)
            ;; The next two forms must be in the order in which they
            ;; appear, since the start breakpoint must run before the
-           ;; function-end breakpoint's start helper (which calls the
+           ;; fun-end breakpoint's start helper (which calls the
            ;; cookie function.) One reason is that cookie function
            ;; requires that the CONDITIONP shared closure variable be
            ;; initialized.
            (sb-di:activate-breakpoint start)
            (sb-di:activate-breakpoint end)))))
 
-      (setf (gethash fun *traced-functions*) info)))
+      (setf (gethash fun *traced-funs*) info)))
 
   function-or-name)
 \f
     current))
 
 ;;; Compute the expansion of TRACE in the non-trivial case (arguments
-;;; specified.) If there are no :FUNCTION specs, then don't use a LET.
-;;; This allows TRACE to be used without the full interpreter.
+;;; specified.) 
 (defun expand-trace (specs)
   (collect ((binds)
            (forms))
           ((and (keywordp name)
                 (not (or (fboundp name) (macro-function name))))
            (error "unknown TRACE option: ~S" name))
+          ((stringp name)
+           (let ((package (find-undeleted-package-or-lose name)))
+             (do-all-symbols (symbol (find-package name))
+               (when (and (eql package (symbol-package symbol))
+                          (fboundp symbol)
+                          (not (macro-function symbol))
+                          (not (special-operator-p symbol)))
+                 (forms `(trace-1 ',symbol ',options))))))
           (t
            (forms `(trace-1 ',name ',options))))
          (setq current (parse-trace-options current options)))))
+    
+    `(let ,(binds)
+      (list ,@(forms)))))
 
-    (if (binds)
-       `(let ,(binds) (list ,@(forms)))
-       `(list ,@(forms)))))
-
-(defun %list-traced-functions ()
-  (loop for x being each hash-value in *traced-functions*
+(defun %list-traced-funs ()
+  (loop for x being each hash-value in *traced-funs*
        collect (trace-info-what x)))
 
 (defmacro trace (&rest specs)
   #+sb-doc
   "TRACE {Option Global-Value}* {Name {Option Value}*}*
-   TRACE is a debugging tool that provides information when specified functions
-   are called. In its simplest form:
-       (trace Name-1 Name-2 ...)
-   (The Names are not evaluated.)
-
-   Options allow modification of the default behavior. Each option is a pair
-   of an option keyword and a value form. Global options are specified before
-   the first name, and affect all functions traced by a given use of TRACE.
-   Options may also be interspersed with function names, in which case they
-   act as local options, only affecting tracing of the immediately preceding
-   function name. Local options override global options.
-
-   By default, TRACE causes a printout on *TRACE-OUTPUT* each time that
-   one of the named functions is entered or returns. (This is the
-   basic, ANSI Common Lisp behavior of TRACE.) As an SBCL extension, the
-   :REPORT SB-EXT:PROFILE option can be used to instead cause information
-   to be silently recorded to be inspected later using the SB-EXT:PROFILE
-   function.
-
-   The following options are defined:
+
+TRACE is a debugging tool that provides information when specified
+functions are called. In its simplest form:
+
+       (TRACE NAME-1 NAME-2 ...)
+
+The NAMEs are not evaluated. Each may be a symbol, denoting an
+individual function, or a string, denoting all functions fbound to
+symbols whose home package is the package with the given name.
+
+Options allow modification of the default behavior. Each option is a
+pair of an option keyword and a value form. Global options are
+specified before the first name, and affect all functions traced by a
+given use of TRACE. Options may also be interspersed with function
+names, in which case they act as local options, only affecting tracing
+of the immediately preceding function name. Local options override
+global options.
+
+By default, TRACE causes a printout on *TRACE-OUTPUT* each time that
+one of the named functions is entered or returns. (This is the basic,
+ANSI Common Lisp behavior of TRACE.) As an SBCL extension, the
+:REPORT SB-EXT:PROFILE option can be used to instead cause information
+to be silently recorded to be inspected later using the SB-EXT:PROFILE
+function.
+
+The following options are defined:
 
    :REPORT Report-Type
        If Report-Type is TRACE (the default) then information is reported
        evaluates to true at the time of the call. :CONDITION-AFTER is
        similar, but suppresses the initial printout, and is tested when the
        function returns. :CONDITION-ALL tries both before and after.
+       This option is not supported with :REPORT PROFILE.
 
    :BREAK Form
    :BREAK-AFTER Form
        In addition to the usual printout, the result of evaluating Form is
        printed at the start of the function, at the end of the function, or
        both, according to the respective option. Multiple print options cause
-       multiple values to be printed.
+       multiple values to be printed. 
 
    :WHEREIN Names
        If specified, Names is a function name or list of names. TRACE does
        nothing unless a call to one of those functions encloses the call to
        this function (i.e. it would appear in a backtrace.)  Anonymous
-       functions have string names like \"DEFUN FOO\". 
+       functions have string names like \"DEFUN FOO\". This option is not
+       supported with :REPORT PROFILE.
 
    :ENCAPSULATE {:DEFAULT | T | NIL}
        If T, the tracing is done via encapsulation (redefining the function
    :FUNCTION Function-Form
        This is a not really an option, but rather another way of specifying
        what function to trace. The Function-Form is evaluated immediately,
-       and the resulting function is traced.
+       and the resulting function is instrumented, i.e. traced or profiled
+       as specified in REPORT.
 
-   :CONDITION, :BREAK and :PRINT forms are evaluated in the lexical environment
-   of the called function; SB-DEBUG:VAR and SB-DEBUG:ARG can be used. The
-   -AFTER and -ALL forms are evaluated in the null environment."
+:CONDITION, :BREAK and :PRINT forms are evaluated in a context which
+mocks up the lexical environment of the called function, so that
+SB-DEBUG:VAR and SB-DEBUG:ARG can be used. The -AFTER and -ALL forms
+are evaluated in the null environment."
   (if specs
       (expand-trace specs)
-      '(%list-traced-functions)))
+      '(%list-traced-funs)))
 \f
 ;;;; untracing
 
 ;;; Untrace one function.
 (defun untrace-1 (function-or-name)
   (let* ((fun (trace-fdefinition function-or-name))
-        (info (gethash fun *traced-functions*)))
+        (info (gethash fun *traced-funs*)))
     (cond
      ((not info)
       (warn "Function is not TRACEd: ~S" function-or-name))
        (sb-di:delete-breakpoint (trace-info-start-breakpoint info))
        (sb-di:delete-breakpoint (trace-info-end-breakpoint info))))
       (setf (trace-info-untraced info) t)
-      (remhash fun *traced-functions*)))))
+      (remhash fun *traced-funs*)))))
 
 ;;; Untrace all traced functions.
 (defun untrace-all ()
-  (dolist (fun (%list-traced-functions))
+  (dolist (fun (%list-traced-funs))
     (untrace-1 fun))
   t)
 
   #+sb-doc
   "Remove tracing from the specified functions. With no args, untrace all
    functions."
+  ;; KLUDGE: Since we now allow (TRACE FOO BAR "SB-EXT") to trace not
+  ;; only #'FOO and #'BAR but also all the functions in #<PACKAGE "SB-EXT">,
+  ;; it would be probably be best for consistency to do something similar
+  ;; with UNTRACE. (But I leave it to someone who uses and cares about
+  ;; UNTRACE-with-args more often than I do.) -- WHN 2003-12-17
   (if specs
       (collect ((res))
        (let ((current specs))