Revert "Clean up %more-arg-values."
[sbcl.git] / src / code / profile.lisp
1 ;;;; This software is part of the SBCL system. See the README file for
2 ;;;; more information.
3 ;;;;
4 ;;;; This software is derived from the CMU CL system, which was
5 ;;;; written at Carnegie Mellon University and released into the
6 ;;;; public domain. The software is in the public domain and is
7 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
8 ;;;; files for more information.
9
10 (in-package "SB-PROFILE") ; (SB-, not SB!, since we're built in warm load.)
11 \f
12
13 ;;;; COUNTER object
14 ;;;;
15 ;;;; Thread safe, and reasonably fast: in common case increment is just an
16 ;;;; ATOMIC-INCF, in overflow case grab a lock and increment overflow counter.
17
18 (declaim (inline make-counter))
19 (defstruct (counter (:constructor make-counter) (:copier nil))
20   (word 0 :type sb-vm:word)
21   (overflow 0 :type unsigned-byte))
22
23 (defun incf-counter (counter delta)
24   ;; When running multi-threaded we can easily get negative numbers for the
25   ;; cons-counter. Don't count them at all.
26   (when (plusp delta)
27     (labels ((%incf-overflow (&optional (n 1))
28                ;; Overflow-counter can run into bignums... so we need to loop
29                ;; around CAS till the increment succeeds.
30                (loop for old = (counter-overflow counter)
31                      until (eq old (compare-and-swap (counter-overflow counter)
32                                                      old (+ old n)))))
33              (%incf (d)
34                ;; Increment the word-sized counter. If it overflows, record the
35                ;; overflow.
36                (let ((prev (atomic-incf (counter-word counter) d)))
37                  (when (< (logand most-positive-word (+ prev d)) prev)
38                    (%incf-overflow)))))
39       ;; DELTA can potentially be a bignum -- cut it down to word-size.
40       (unless (typep delta 'sb-vm:word)
41         (multiple-value-bind (n r) (truncate delta (1+ most-positive-word))
42           (%incf-overflow n)
43           (setf delta r)))
44       ;; ATOMIC-INCF can at most handle SIGNED-WORD: if DELTA doesn't fit that,
45       ;; DELTA/2 will.
46       (if (typep delta 'sb-vm:signed-word)
47           (%incf delta)
48           ;; ...and if delta is still too big, split it into four parts: they
49           ;; are guaranteed to fit into a signed word.
50           (multiple-value-bind (n r) (truncate delta 2)
51             (%incf n)
52             (%incf n)
53             (%incf r)))))
54   counter)
55
56 (defun counter-count (counter)
57   (+ (counter-word counter)
58      (* (counter-overflow counter) (1+ most-positive-word))))
59 \f
60 ;;;; High resolution timer
61
62 ;;; FIXME: High resolution this is not. Build a microsecond-accuracy version
63 ;;; on top of unix-getrusage, maybe.
64
65 (defconstant +ticks-per-second+ internal-time-units-per-second)
66
67 (declaim (inline get-internal-ticks))
68 (defun get-internal-ticks ()
69   (get-internal-run-time))
70 \f
71 ;;;; global data structures
72
73 ;;; We associate a PROFILE-INFO structure with each profiled function
74 ;;; name. This holds the functions that we call to manipulate the
75 ;;; closure which implements the encapsulation.
76 (defvar *profiled-fun-name->info*
77   (make-hash-table
78    ;; EQL testing isn't good enough for generalized function names
79    ;; like (SETF FOO).
80    :test 'equal
81    :synchronized t))
82 (defstruct (profile-info (:copier nil))
83   (name              (missing-arg) :read-only t)
84   (encapsulated-fun  (missing-arg) :type function :read-only t)
85   (encapsulation-fun (missing-arg) :type function :read-only t)
86   (read-stats-fun    (missing-arg) :type function :read-only t)
87   (clear-stats-fun   (missing-arg) :type function :read-only t))
88
89 ;;; These variables are used to subtract out the time and consing for
90 ;;; recursive and other dynamically nested profiled calls. The total
91 ;;; resource consumed for each nested call is added into the
92 ;;; appropriate variable. When the outer function returns, these
93 ;;; amounts are subtracted from the total.
94 (declaim (counter *enclosed-ticks* *enclosed-consing*))
95 (defvar *enclosed-ticks*)
96 (defvar *enclosed-consing*)
97
98 ;;; This variable is also used to subtract out time for nested
99 ;;; profiled calls. The time inside the profile wrapper call --
100 ;;; between its two calls to GET-INTERNAL-TICKS -- is accounted
101 ;;; for by the *ENCLOSED-TIME* variable. However, there's also extra
102 ;;; overhead involved, before we get to the first call to
103 ;;; GET-INTERNAL-TICKS, and after we get to the second call. By
104 ;;; keeping track of the count of enclosed profiled calls, we can try
105 ;;; to compensate for that.
106 (declaim (counter *enclosed-profiles*))
107 (defvar *enclosed-profiles*)
108
109 (declaim (counter *enclosed-gc-run-time*))
110 (defvar *enclosed-gc-run-time*)
111
112 ;;; the encapsulated function we're currently computing profiling data
113 ;;; for, recorded so that we can detect the problem of
114 ;;; PROFILE-computing machinery calling a function which has itself
115 ;;; been PROFILEd
116 (defvar *computing-profiling-data-for*)
117
118 ;;; the components of profiling overhead
119 (defstruct (overhead (:copier nil))
120   ;; the number of ticks a bare function call takes. This is
121   ;; factored into the other overheads, but not used for itself.
122   (call (missing-arg) :type single-float :read-only t)
123   ;; the number of ticks that will be charged to a profiled
124   ;; function due to the profiling code
125   (internal (missing-arg) :type single-float :read-only t)
126   ;; the number of ticks of overhead for profiling that a single
127   ;; profiled call adds to the total runtime for the program
128   (total (missing-arg) :type single-float :read-only t))
129 (defvar *overhead*)
130 (declaim (type overhead *overhead*))
131 (makunbound '*overhead*) ; in case we reload this file when tweaking
132 \f
133 ;;;; profile encapsulations
134
135 ;;; Return a collection of closures over the same lexical context,
136 ;;;   (VALUES ENCAPSULATION-FUN READ-STATS-FUN CLEAR-STATS-FUN).
137 ;;;
138 ;;; ENCAPSULATION-FUN is a plug-in replacement for ENCAPSULATED-FUN,
139 ;;; which updates statistics whenever it's called.
140 ;;;
141 ;;; READ-STATS-FUN returns the statistics:
142 ;;;   (VALUES COUNT TIME CONSING PROFILE).
143 ;;; COUNT is the count of calls to ENCAPSULATION-FUN. TICKS is
144 ;;; the total number of ticks spent in ENCAPSULATED-FUN.
145 ;;; CONSING is the total consing of ENCAPSULATION-FUN. PROFILE is the
146 ;;; number of calls to the profiled function, stored for the purposes
147 ;;; of trying to estimate that part of profiling overhead which occurs
148 ;;; outside the interval between the profile wrapper function's timer
149 ;;; calls.
150 ;;;
151 ;;; CLEAR-STATS-FUN clears the statistics.
152 ;;;
153 ;;; (The reason for implementing this as coupled closures, with the
154 ;;; counts built into the lexical environment, is that we hope this
155 ;;; will minimize profiling overhead.)
156 (defun profile-encapsulation-lambdas (encapsulated-fun)
157   (declare (type function encapsulated-fun))
158   (let* ((count (make-counter))
159          (ticks (make-counter))
160          (consing (make-counter))
161          (profiles (make-counter))
162          (gc-run-time (make-counter)))
163     (declare (counter count ticks consing profiles gc-run-time))
164     (values
165      ;; ENCAPSULATION-FUN
166      (lambda (&more arg-context arg-count)
167        (declare (optimize speed safety))
168        ;; Make sure that we're not recursing infinitely.
169        (when (boundp '*computing-profiling-data-for*)
170          (unprofile-all) ; to avoid further recursion
171          (error "~@<When computing profiling data for ~S, the profiled ~
172                     function ~S was called. To get out of this infinite recursion, all ~
173                     functions have been unprofiled. (Since the profiling system evidently ~
174                     uses ~S in its computations, it looks as though it's a bad idea to ~
175                     profile it.)~:@>"
176                 *computing-profiling-data-for* encapsulated-fun
177                 encapsulated-fun))
178        (incf-counter count 1)
179        (let ((dticks 0)
180              (dconsing 0)
181              (inner-enclosed-profiles 0)
182              (dgc-run-time 0))
183          (declare (truly-dynamic-extent dticks dconsing inner-enclosed-profiles))
184          (unwind-protect
185              (let* ((start-ticks (get-internal-ticks))
186                     (start-gc-run-time *gc-run-time*)
187                     (*enclosed-ticks* (make-counter))
188                     (*enclosed-consing* (make-counter))
189                     (*enclosed-profiles* (make-counter))
190                     (nbf0 *n-bytes-freed-or-purified*)
191                     (dynamic-usage-0 (sb-kernel:dynamic-usage))
192                     (*enclosed-gc-run-time* (make-counter)))
193                (declare (dynamic-extent *enclosed-ticks* *enclosed-consing* *enclosed-profiles* *enclosed-gc-run-time*))
194                (unwind-protect
195                    (multiple-value-call encapsulated-fun
196                                         (sb-c:%more-arg-values arg-context
197                                                                0
198                                                                arg-count))
199                  (let ((*computing-profiling-data-for* encapsulated-fun)
200                        (dynamic-usage-1 (sb-kernel:dynamic-usage)))
201                    (setf dticks (- (get-internal-ticks) start-ticks)
202                          dconsing (if (eql *n-bytes-freed-or-purified* nbf0)
203                                       ;; common special case where we can avoid
204                                       ;; bignum arithmetic
205                                       (- dynamic-usage-1 dynamic-usage-0)
206                                       ;; general case
207                                       (- (get-bytes-consed) nbf0 dynamic-usage-0))
208                          inner-enclosed-profiles (counter-count *enclosed-profiles*)
209                          dgc-run-time (- *gc-run-time* start-gc-run-time))
210                    (incf-counter ticks (- dticks (counter-count *enclosed-ticks*)))
211                    (incf-counter gc-run-time (- dgc-run-time (counter-count *enclosed-gc-run-time*)))
212                    (incf-counter consing (- dconsing (counter-count *enclosed-consing*)))
213                    (incf-counter profiles inner-enclosed-profiles))))
214            (when (boundp '*enclosed-ticks*)
215              (incf-counter *enclosed-ticks* dticks)
216              (incf-counter *enclosed-consing* dconsing)
217              (incf-counter *enclosed-profiles* (1+ inner-enclosed-profiles))
218              (incf-counter *enclosed-gc-run-time* dgc-run-time)))))
219      ;; READ-STATS-FUN
220      (lambda ()
221        (values (counter-count count)
222                (counter-count ticks)
223                (counter-count consing)
224                (counter-count profiles)
225                (counter-count gc-run-time)))
226      ;; CLEAR-STATS-FUN
227      (lambda ()
228        (setf count (make-counter)
229              ticks (make-counter)
230              consing (make-counter)
231              profiles (make-counter)
232              gc-run-time (make-counter))))))
233 \f
234 ;;;; interfaces
235
236 ;;; A symbol or (SETF FOO) list names a function, a string names all
237 ;;; the functions named by symbols in the named package.
238 (defun mapc-on-named-funs (function names)
239   (dolist (name names)
240     (etypecase name
241       (symbol (funcall function name))
242       (list
243        (legal-fun-name-or-type-error name)
244        ;; Then we map onto it.
245        (funcall function name))
246       (string (let ((package (find-undeleted-package-or-lose name)))
247                 (do-symbols (symbol package)
248                   (when (eq (symbol-package symbol) package)
249                     (when (and (fboundp symbol)
250                                (not (macro-function symbol))
251                                (not (special-operator-p symbol)))
252                       (funcall function symbol))
253                     (let ((setf-name `(setf ,symbol)))
254                       (when (fboundp setf-name)
255                         (funcall function setf-name)))))))))
256   (values))
257
258 ;;; Profile the named function, which should exist and not be profiled
259 ;;; already.
260 (defun profile-1-unprofiled-fun (name)
261   (let ((encapsulated-fun (fdefinition name)))
262     (multiple-value-bind (encapsulation-fun read-stats-fun clear-stats-fun)
263         (profile-encapsulation-lambdas encapsulated-fun)
264       (without-package-locks
265        (setf (fdefinition name)
266              encapsulation-fun))
267       (setf (gethash name *profiled-fun-name->info*)
268             (make-profile-info :name name
269                                :encapsulated-fun encapsulated-fun
270                                :encapsulation-fun encapsulation-fun
271                                :read-stats-fun read-stats-fun
272                                :clear-stats-fun clear-stats-fun))
273       (values))))
274
275 ;;; Profile the named function. If already profiled, unprofile first.
276 (defun profile-1-fun (name)
277   (cond ((fboundp name)
278          (when (gethash name *profiled-fun-name->info*)
279            (warn "~S is already profiled, so unprofiling it first." name)
280            (unprofile-1-fun name))
281          (profile-1-unprofiled-fun name))
282         (t
283          (warn "ignoring undefined function ~S" name)))
284   (values))
285
286 ;;; Unprofile the named function, if it is profiled.
287 (defun unprofile-1-fun (name)
288   (let ((pinfo (gethash name *profiled-fun-name->info*)))
289     (cond (pinfo
290            (remhash name *profiled-fun-name->info*)
291            (if (eq (fdefinition name) (profile-info-encapsulation-fun pinfo))
292                (without-package-locks
293                 (setf (fdefinition name) (profile-info-encapsulated-fun pinfo)))
294                (warn "preserving current definition of redefined function ~S"
295                      name)))
296           (t
297            (warn "~S is not a profiled function." name))))
298   (values))
299
300 (defmacro profile (&rest names)
301   #+sb-doc
302   "PROFILE Name*
303
304    If no names are supplied, return the list of profiled functions.
305
306    If names are supplied, wrap profiling code around the named functions.
307    As in TRACE, the names are not evaluated. A symbol names a function.
308    A string names all the functions named by symbols in the named
309    package. If a function is already profiled, then unprofile and
310    reprofile (useful to notice function redefinition.)  If a name is
311    undefined, then we give a warning and ignore it. See also
312    UNPROFILE, REPORT and RESET."
313   (if (null names)
314       `(loop for k being each hash-key in *profiled-fun-name->info*
315              collecting k)
316       `(mapc-on-named-funs #'profile-1-fun ',names)))
317
318 (defmacro unprofile (&rest names)
319   #+sb-doc
320   "Unwrap any profiling code around the named functions, or if no names
321   are given, unprofile all profiled functions. A symbol names
322   a function. A string names all the functions named by symbols in the
323   named package. NAMES defaults to the list of names of all currently
324   profiled functions."
325   (if names
326       `(mapc-on-named-funs #'unprofile-1-fun ',names)
327       `(unprofile-all)))
328
329 (defun unprofile-all ()
330   (dohash ((name profile-info) *profiled-fun-name->info*
331            :locked t)
332     (declare (ignore profile-info))
333     (unprofile-1-fun name)))
334
335 (defun reset ()
336   "Reset the counters for all profiled functions."
337   (dohash ((name profile-info) *profiled-fun-name->info* :locked t)
338     (declare (ignore name))
339     (funcall (profile-info-clear-stats-fun profile-info))))
340 \f
341 ;;;; reporting results
342
343 (defstruct (time-info (:copier nil))
344   name
345   calls
346   seconds
347   consing
348   gc-run-time)
349
350 ;;; Return our best guess for the run time in a function, subtracting
351 ;;; out factors for profiling overhead. We subtract out the internal
352 ;;; overhead for each call to this function, since the internal
353 ;;; overhead is the part of the profiling overhead for a function that
354 ;;; is charged to that function.
355 ;;;
356 ;;; We also subtract out a factor for each call to a profiled function
357 ;;; within this profiled function. This factor is the total profiling
358 ;;; overhead *minus the internal overhead*. We don't subtract out the
359 ;;; internal overhead, since it was already subtracted when the nested
360 ;;; profiled functions subtracted their running time from the time for
361 ;;; the enclosing function.
362 (defun compensate-time (calls ticks profile)
363   (let ((raw-compensated
364          (- (/ (float ticks) (float +ticks-per-second+))
365             (* (overhead-internal *overhead*) (float calls))
366             (* (- (overhead-total *overhead*)
367                   (overhead-internal *overhead*))
368                (float profile)))))
369     (max raw-compensated 0.0)))
370
371 (defun report (&key limit (print-no-call-list t))
372   "Report results from profiling. The results are approximately
373 adjusted for profiling overhead. The compensation may be rather
374 inaccurate when bignums are involved in runtime calculation, as in a
375 very-long-running Lisp process.
376
377 If LIMIT is set to an integer, only the top LIMIT results are
378 reported. If PRINT-NO-CALL-LIST is T (the default) then a list of
379 uncalled profiled functions are listed."
380   (unless (boundp '*overhead*)
381     (setf *overhead*
382           (compute-overhead)))
383   (let ((time-info-list ())
384         (no-call-name-list ()))
385     (dohash ((name pinfo) *profiled-fun-name->info* :locked t)
386       (unless (eq (fdefinition name)
387                   (profile-info-encapsulation-fun pinfo))
388         (warn "Function ~S has been redefined, so times may be inaccurate.~@
389                PROFILE it again to record calls to the new definition."
390               name))
391       (multiple-value-bind (calls ticks consing profile gc-run-time)
392           (funcall (profile-info-read-stats-fun pinfo))
393         (if (zerop calls)
394             (push name no-call-name-list)
395             (push (make-time-info :name name
396                                   :calls calls
397                                   :seconds (compensate-time calls
398                                                             ticks
399                                                             profile)
400                                   :consing consing
401                                   :gc-run-time gc-run-time)
402                   time-info-list))))
403
404     (let ((times
405            (sort time-info-list
406                  #'>=
407                  :key #'time-info-seconds)))
408       (print-profile-table
409        (if (and limit (> (length times) limit))
410            (subseq times 0 limit)
411            times)))
412
413     (when (and print-no-call-list no-call-name-list)
414       (format *trace-output*
415               "~%These functions were not called:~%~{~<~%~:; ~S~>~}~%"
416               (sort no-call-name-list #'string<
417                     :key (lambda (name)
418                            (symbol-name (fun-name-block-name name))))))
419
420     (values)))
421
422
423 (defun print-profile-table (time-info-list)
424   (let ((total-seconds 0.0)
425         (total-consed 0)
426         (total-calls 0)
427         (total-gc-run-time 0)
428         (seconds-width (length "seconds"))
429         (consed-width (length "consed"))
430         (calls-width (length "calls"))
431         (sec/call-width 10)
432         (gc-run-time-width (length "gc"))
433         (name-width 6))
434     (dolist (time-info time-info-list)
435       (incf total-seconds (time-info-seconds time-info))
436       (incf total-consed (time-info-consing time-info))
437       (incf total-calls (time-info-calls time-info))
438       (incf total-gc-run-time (time-info-gc-run-time time-info)))
439     (setf seconds-width (max (length (format nil "~10,3F" total-seconds))
440                              seconds-width)
441           calls-width (max (length (format nil "~:D" total-calls))
442                            calls-width)
443           consed-width (max (length (format nil "~:D" total-consed))
444                             consed-width)
445           gc-run-time-width (max (length (format nil "~10,3F" (/ total-gc-run-time internal-time-units-per-second)))
446                             gc-run-time-width))
447
448     (flet ((dashes ()
449              (dotimes (i (+ seconds-width consed-width calls-width
450                             sec/call-width name-width
451                             (* 5 3)))
452                (write-char #\- *trace-output*))
453              (terpri *trace-output*)))
454       (format *trace-output* "~&~@{ ~v:@<~A~>~^|~}~%"
455               seconds-width "seconds"
456               (1+ gc-run-time-width) "gc"
457               (1+ consed-width) "consed"
458               (1+ calls-width) "calls"
459               (1+ sec/call-width) "sec/call"
460               (1+ name-width) "name")
461
462       (dashes)
463
464       (dolist (time-info time-info-list)
465         (format *trace-output* "~v,3F | ~v,3F | ~v:D | ~v:D | ~10,6F | ~S~%"
466                 seconds-width (time-info-seconds time-info)
467                 gc-run-time-width (/ (time-info-gc-run-time time-info) internal-time-units-per-second)
468                 consed-width (time-info-consing time-info)
469                 calls-width (time-info-calls time-info)
470                 (/ (time-info-seconds time-info)
471                    (float (time-info-calls time-info)))
472                 (time-info-name time-info)))
473
474       (dashes)
475
476       (format *trace-output* "~v,3F | ~v,3F | ~v:D | ~v:D |            | Total~%"
477                 seconds-width total-seconds
478                 gc-run-time-width (/ total-gc-run-time internal-time-units-per-second)
479                 consed-width total-consed
480                 calls-width total-calls)
481
482       (format *trace-output*
483               "~%estimated total profiling overhead: ~4,2F seconds~%"
484               (* (overhead-total *overhead*) (float total-calls)))
485       (format *trace-output*
486               "~&overhead estimation parameters:~%  ~Ss/call, ~Ss total profiling, ~Ss internal profiling~%"
487               (overhead-call *overhead*)
488               (overhead-total *overhead*)
489               (overhead-internal *overhead*)))))
490
491 \f
492 ;;;; overhead estimation
493
494 ;;; We average the timing overhead over this many iterations.
495 ;;;
496 ;;; (This is a variable, not a constant, so that it can be set in
497 ;;; .sbclrc if desired. Right now, that's an unsupported extension
498 ;;; that I (WHN) use for my own experimentation, but it might
499 ;;; become supported someday. Comments?)
500 (declaim (type unsigned-byte *timer-overhead-iterations*))
501 (defparameter *timer-overhead-iterations*
502   500000)
503
504 ;;; a dummy function that we profile to find profiling overhead
505 (declaim (notinline compute-overhead-aux))
506 (defun compute-overhead-aux (x)
507   (declare (ignore x)))
508
509 ;;; Return a newly computed OVERHEAD object.
510 (defun compute-overhead ()
511   (format *debug-io* "~&measuring PROFILE overhead..")
512   (flet ((frob ()
513            (let ((start (get-internal-ticks))
514                  (fun (symbol-function 'compute-overhead-aux)))
515              (declare (type function fun))
516              (dotimes (i *timer-overhead-iterations*)
517                (funcall fun fun))
518              (/ (float (- (get-internal-ticks) start))
519                 (float +ticks-per-second+)
520                 (float *timer-overhead-iterations*)))))
521     (let (;; Measure unprofiled calls to estimate call overhead.
522           (call-overhead (frob))
523           total-overhead
524           internal-overhead)
525       ;; Measure profiled calls to estimate profiling overhead.
526       (unwind-protect
527           (progn
528             (profile compute-overhead-aux)
529             (setf total-overhead
530                   (- (frob) call-overhead)))
531         (let* ((pinfo (gethash 'compute-overhead-aux
532                                *profiled-fun-name->info*))
533                (read-stats-fun (profile-info-read-stats-fun pinfo))
534                (time (nth-value 1 (funcall read-stats-fun))))
535           (setf internal-overhead
536                 (/ (float time)
537                    (float +ticks-per-second+)
538                    (float *timer-overhead-iterations*))))
539         (unprofile compute-overhead-aux))
540       (prog1
541           (make-overhead :call call-overhead
542                          :total total-overhead
543                          :internal internal-overhead)
544         (format *debug-io* "done~%")))))
545
546 ;;; It would be bad to compute *OVERHEAD*, save it into a .core file,
547 ;;; then load the old *OVERHEAD* value from the .core file into a
548 ;;; different machine running at a different speed. We avoid this by
549 ;;; erasing *CALL-OVERHEAD* whenever we save a .core file.
550 (defun profile-deinit ()
551   (without-package-locks
552     (makunbound '*overhead*)))