47414e05ef410cb40b5ee73876e97e0fcb321b58
[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")
11 \f
12 ;;;; reading internal run time with high resolution and low overhead
13
14 ;;; FIXME: It might make sense to replace this with something
15 ;;; with finer resolution, e.g. milliseconds or microseconds.
16 ;;; For that matter, maybe we should boost the internal clock
17 ;;; up to something faster, like milliseconds.
18
19 (defconstant +ticks-per-second+ internal-time-units-per-second)
20
21 (declaim (inline get-internal-ticks))
22 (defun get-internal-ticks () (get-internal-run-time))
23 \f
24 ;;;; PCOUNTER
25
26 ;;; a PCOUNTER is used to represent an unsigned integer quantity which
27 ;;; can grow bigger than a fixnum, but typically does so, if at all,
28 ;;; in many small steps, where we don't want to cons on every step.
29 ;;; (Total system consing, time spent in a profiled function, and
30 ;;; bytes consed in a profiled function are all examples of such
31 ;;; quantities.)
32 (defstruct (pcounter (:copier nil))
33   (integer 0 :type unsigned-byte)
34   (fixnum 0 :type (and fixnum unsigned-byte)))
35
36 (declaim (ftype (function (pcounter integer) pcounter) incf-pcounter))
37 ;;;(declaim (inline incf-pcounter)) ; FIXME: maybe inline when more stable
38 (defun incf-pcounter (pcounter delta)
39   (let ((sum (+ (pcounter-fixnum pcounter) delta)))
40     (cond ((typep sum 'fixnum)
41            (setf (pcounter-fixnum pcounter) sum))
42           (t
43            (incf (pcounter-integer pcounter) sum)
44            (setf (pcounter-fixnum pcounter) 0))))
45   pcounter)
46
47 (declaim (ftype (function (pcounter) integer) pcounter->integer))
48 ;;;(declaim (inline pcounter->integer)) ; FIXME: maybe inline when more stable
49 (defun pcounter->integer (pcounter)
50   (+ (pcounter-integer pcounter)
51      (pcounter-fixnum pcounter)))
52 \f
53 ;;;; operations on (OR PCOUNTER FIXNUM)
54 ;;;;
55 ;;;; When we don't want to cons a PCOUNTER unless we're forced to, we
56 ;;;; start with a FIXNUM counter and only create a PCOUNTER if the
57 ;;;; FIXNUM overflows.
58
59 (declaim (ftype (function ((or pcounter fixnum) integer) (or pcounter fixnum)) %incf-pcounter-or-fixnum))
60 ;;;(declaim (inline %incf-pcounter-or-fixnum)) ; FIXME: maybe inline when more stable
61 (defun %incf-pcounter-or-fixnum (x delta)
62   (etypecase x
63     (fixnum
64      (let ((sum (+ x delta)))
65        (if (typep sum 'fixnum)
66            sum
67            (make-pcounter :integer sum))))
68     (pcounter
69      (incf-pcounter x delta))))
70   
71 (define-modify-macro incf-pcounter-or-fixnum (delta) %incf-pcounter-or-fixnum)
72
73 ;;; Trade off space for execution time by handling the common fast
74 ;;; (TYPEP DELTA 'FIXNUM) case inline and only calling generic
75 ;;; arithmetic as a last resort.
76 (defmacro fastbig-incf-pcounter-or-fixnum (x delta)
77   (once-only ((delta delta))
78     `(etypecase ,delta
79        (fixnum (incf-pcounter-or-fixnum ,x ,delta))
80        (integer (incf-pcounter-or-fixnum ,x ,delta)))))
81
82 (declaim (ftype (function ((or pcounter fixnum)) integer) pcounter-or-fixnum->integer))
83 (declaim (maybe-inline pcounter-or-fixnum->integer))
84 (defun pcounter-or-fixnum->integer (x)
85   (etypecase x
86     (fixnum x)
87     (pcounter (pcounter->integer x))))
88 \f
89 ;;;; implementation-dependent interfaces
90
91 #|
92 ;;; To avoid unnecessary consing in the "encapsulation" code, we want
93 ;;; find out the number of required arguments, and use &REST to
94 ;;; capture only non-required arguments. This function returns (VALUES
95 ;;; MIN-ARGS OPTIONALS-P), where MIN-ARGS is the number of required
96 ;;; arguments and OPTIONALS-P is true iff there are any non-required
97 ;;; arguments (such as &OPTIONAL, &REST, or &KEY).
98 (declaim (ftype (function ((or symbol cons)) (values fixnum t)) fun-signature))
99 (defun fun-signature (name)
100   (let ((type (info :function :type name)))
101     (cond ((not (function-type-p type))
102            (values 0 t))
103           (t
104            (values (length (function-type-required type))
105                    (or (function-type-optional type)
106                        (function-type-keyp type)
107                        (function-type-rest type)))))))
108 |#
109 \f
110 ;;;; global data structures
111
112 ;;; We associate a PROFILE-INFO structure with each profiled function
113 ;;; name. This holds the functions that we call to manipulate the
114 ;;; closure which implements the encapsulation.
115 (defvar *profiled-function-name->info* (make-hash-table))
116 (defstruct (profile-info (:copier nil))
117   (name              (required-argument) :read-only t)
118   (encapsulated-fun  (required-argument) :type function :read-only t)
119   (encapsulation-fun (required-argument) :type function :read-only t)
120   (read-stats-fun    (required-argument) :type function :read-only t)
121   (clear-stats-fun   (required-argument) :type function :read-only t))
122
123 ;;; These variables are used to subtract out the time and consing for
124 ;;; recursive and other dynamically nested profiled calls. The total
125 ;;; resource consumed for each nested call is added into the
126 ;;; appropriate variable. When the outer function returns, these
127 ;;; amounts are subtracted from the total.
128 (defvar *enclosed-ticks* 0)
129 (defvar *enclosed-consing* 0)
130 (declaim (type (or pcounter fixnum) *enclosed-ticks* *enclosed-consing*))
131
132 ;;; This variable is also used to subtract out time for nested
133 ;;; profiled calls. The time inside the profile wrapper call --
134 ;;; between its two calls to GET-INTERNAL-TICKS -- is accounted
135 ;;; for by the *ENCLOSED-TIME* variable. However, there's also extra
136 ;;; overhead involved, before we get to the first call to
137 ;;; GET-INTERNAL-TICKS, and after we get to the second call. By
138 ;;; keeping track of the count of enclosed profiled calls, we can try
139 ;;; to compensate for that.
140 (defvar *enclosed-profiles* 0)
141 (declaim (type (or pcounter fixnum) *enclosed-profiles*))
142
143 ;;; the components of profiling overhead
144 (defstruct (overhead (:copier nil))
145   ;; the number of ticks a bare function call takes. This is
146   ;; factored into the other overheads, but not used for itself.
147   (call (required-argument) :type single-float :read-only t)
148   ;; the number of ticks that will be charged to a profiled
149   ;; function due to the profiling code
150   (internal (required-argument) :type single-float :read-only t)
151   ;; the number of ticks of overhead for profiling that a single
152   ;; profiled call adds to the total runtime for the program
153   (total (required-argument) :type single-float :read-only t))
154 (defvar *overhead*)
155 (declaim (type overhead *overhead*))
156 \f
157 ;;;; profile encapsulations
158
159 ;;; Trade off space for time by handling the usual all-FIXNUM cases
160 ;;; inline.
161 (defmacro fastbig- (x y)
162   (once-only ((x x) (y y))
163     `(if (and (typep ,x 'fixnum)
164               (typep ,y 'fixnum))
165          (- ,x ,y)
166          (- ,x ,y))))
167 (defmacro fastbig-1+ (x)
168   (once-only ((x x))
169     `(if (typep ,x 'index)
170          (1+ ,x)
171          (1+ ,x))))
172
173 ;;; Return a collection of closures over the same lexical context,
174 ;;;   (VALUES ENCAPSULATION-FUN READ-STATS-FUN CLEAR-STATS-FUN).
175 ;;;
176 ;;; ENCAPSULATION-FUN is a plug-in replacement for ENCAPSULATED-FUN,
177 ;;; which updates statistics whenver it's called.
178 ;;;
179 ;;; READ-STATS-FUN returns the statistics:
180 ;;;   (VALUES COUNT TIME CONSING PROFILE).
181 ;;; COUNT is the count of calls to ENCAPSULATION-FUN. TICKS is
182 ;;; the total number of ticks spent in ENCAPSULATED-FUN.
183 ;;; CONSING is the total consing of ENCAPSULATION-FUN. PROFILE is the
184 ;;; number of calls to the profiled function, stored for the purposes
185 ;;; of trying to estimate that part of profiling overhead which occurs
186 ;;; outside the interval between the profile wrapper function's timer
187 ;;; calls.
188 ;;;
189 ;;; CLEAR-STATS-FUN clears the statistics.
190 ;;;
191 ;;; (The reason for implementing this as coupled closures, with the
192 ;;; counts built into the lexical environment, is that we hope this
193 ;;; will minimize profiling overhead.)
194 (defun profile-encapsulation-lambdas (encapsulated-fun)
195   (declare (type function encapsulated-fun))
196   (declare (optimize speed safety))
197   (let* ((count 0)
198          (ticks 0)
199          (consing 0)
200          (profiles 0))
201     (declare (type (or pcounter fixnum) count ticks consing profiles))
202     (values
203      ;; ENCAPSULATION-FUN
204      (lambda (sb-c:&more arg-context arg-count)
205        #+nil (declare (optimize (speed 3) (safety 0))) ; FIXME: remove #+NIL?
206        (fastbig-incf-pcounter-or-fixnum count 1)
207        (let ((dticks 0)
208              (dconsing 0)
209              (inner-enclosed-profiles 0))
210          (declare (type unsigned-byte dticks dconsing))
211          (declare (type unsigned-byte inner-enclosed-profiles))
212          (multiple-value-prog1
213              (let ((start-ticks (get-internal-ticks))
214                    ;; KLUDGE: We add (THE UNSIGNED-BYTE ..) wrappers
215                    ;; around GET-BYTES-CONSED because as of
216                    ;; sbcl-0.6.4, at the time that the FTYPE of
217                    ;; GET-BYTES-CONSED is DECLAIMed, the
218                    ;; cross-compiler's type system isn't mature enough
219                    ;; to do anything about it. -- WHN 20000503
220                    (start-consing (the unsigned-byte (get-bytes-consed)))
221                    (*enclosed-ticks* 0)
222                    (*enclosed-consing* 0)
223                    (*enclosed-profiles* 0))
224                (declare (inline pcounter-or-fixnum->integer))
225                (multiple-value-prog1
226                    (multiple-value-call encapsulated-fun
227                                         (sb-c:%more-arg-values arg-context
228                                                                0
229                                                                arg-count))
230                  (setf dticks (fastbig- (get-internal-ticks) start-ticks)
231                        dconsing (fastbig- (the unsigned-byte
232                                                (get-bytes-consed))
233                                           start-consing))
234                  (setf inner-enclosed-profiles
235                        (pcounter-or-fixnum->integer *enclosed-profiles*))
236                  (fastbig-incf-pcounter-or-fixnum ticks (fastbig-
237                                                          dticks
238                                                          *enclosed-ticks*))
239                  (fastbig-incf-pcounter-or-fixnum consing
240                                                   (fastbig-
241                                                    dconsing
242                                                    *enclosed-consing*))
243                  (fastbig-incf-pcounter-or-fixnum profiles
244                                                   inner-enclosed-profiles)))
245            (fastbig-incf-pcounter-or-fixnum *enclosed-ticks* dticks)
246            (fastbig-incf-pcounter-or-fixnum *enclosed-consing* dconsing)
247            (fastbig-incf-pcounter-or-fixnum *enclosed-profiles*
248                                             (fastbig-1+
249                                              inner-enclosed-profiles)))))
250      ;; READ-STATS-FUN
251      (lambda ()
252        (values (pcounter-or-fixnum->integer count)
253                (pcounter-or-fixnum->integer ticks)
254                (pcounter-or-fixnum->integer consing)
255                (pcounter-or-fixnum->integer profiles)))
256      ;; CLEAR-STATS-FUN
257      (lambda ()
258        (setf count 0
259              ticks 0
260              consing 0
261              profiles 0)))))
262 \f
263 ;;; interfaces
264
265 ;;; A symbol or (SETF FOO) list names a function, a string names all
266 ;;; the functions named by symbols in the named package.
267 (defun mapc-on-named-functions (function names)
268   (dolist (name names)
269     (etypecase name
270       (symbol (funcall function name))
271       (list
272        ;; We call this just for the side effect of checking that
273        ;; NAME is a legal function name:
274        (function-name-block-name name)
275        ;; Then we map onto it.
276        (funcall function name))
277       (string (let ((package (find-undeleted-package-or-lose name)))
278                 (do-symbols (symbol package)
279                   (when (eq (symbol-package symbol) package)
280                     (when (fboundp symbol)
281                       (funcall function symbol))
282                     (let ((setf-name `(setf ,symbol)))
283                       (when (fboundp setf-name)
284                         (funcall function setf-name)))))))))
285   (values))
286
287 ;;; Profile the named function, which should exist and not be profiled
288 ;;; already.
289 (defun profile-1-unprofiled-function (name)
290   (let ((encapsulated-fun (fdefinition name)))
291     (multiple-value-bind (encapsulation-fun read-stats-fun clear-stats-fun)
292         (profile-encapsulation-lambdas encapsulated-fun)
293       (setf (fdefinition name)
294             encapsulation-fun)
295       (setf (gethash name *profiled-function-name->info*)
296             (make-profile-info :name name
297                                :encapsulated-fun encapsulated-fun
298                                :encapsulation-fun encapsulation-fun
299                                :read-stats-fun read-stats-fun
300                                :clear-stats-fun clear-stats-fun))
301       (values))))
302
303 ;;; Profile the named function. If already profiled, unprofile first.
304 (defun profile-1-function (name)
305   (cond ((fboundp name)
306          (when (gethash name *profiled-function-name->info*)
307            (warn "~S is already profiled, so unprofiling it first." name)
308            (unprofile-1-function name))
309          (profile-1-unprofiled-function name))
310         (t
311          (warn "ignoring undefined function ~S" name)))
312   (values))
313
314 ;;; Unprofile the named function, if it is profiled.
315 (defun unprofile-1-function (name)
316   (let ((pinfo (gethash name *profiled-function-name->info*)))
317     (cond (pinfo
318            (remhash name *profiled-function-name->info*)
319            (if (eq (fdefinition name) (profile-info-encapsulation-fun pinfo))
320                (setf (fdefinition name) (profile-info-encapsulated-fun pinfo))
321                (warn "preserving current definition of redefined function ~S"
322                      name)))
323           (t
324            (warn "~S is not a profiled function." name))))
325   (values))
326
327 (defmacro profile (&rest names)
328   #+sb-doc
329   "PROFILE Name*
330
331    If no names are supplied, return the list of profiled functions.
332
333    If names are supplied, wrap profiling code around the named functions.
334    As in TRACE, the names are not evaluated. A symbol names a function.
335    A string names all the functions named by symbols in the named
336    package. If a function is already profiled, then unprofile and
337    reprofile (useful to notice function redefinition.)  If a name is
338    undefined, then we give a warning and ignore it. See also
339    UNPROFILE, REPORT and RESET."
340   (if (null names)
341       `(loop for k being each hash-key in *profiled-function-name->info*
342              collecting k)
343       `(mapc-on-named-functions #'profile-1-function ',names)))
344
345 (defmacro unprofile (&rest names)
346   #+sb-doc
347   "Unwrap any profiling code around the named functions, or if no names
348   are given, unprofile all profiled functions. A symbol names
349   a function. A string names all the functions named by symbols in the
350   named package. NAMES defaults to the list of names of all currently 
351   profiled functions."
352   (if names
353       `(mapc-on-named-functions #'unprofile-1-function ',names)
354       `(unprofile-all)))
355
356 (defun unprofile-all ()
357   (dohash (name profile-info *profiled-function-name->info*)
358     (declare (ignore profile-info))
359     (unprofile-1-function name)))
360
361 (defun reset ()
362   "Reset the counters for all profiled functions."
363   (dohash (name profile-info *profiled-function-name->info*)
364     (declare (ignore name))
365     (funcall (profile-info-clear-stats-fun profile-info))))
366 \f
367 ;;;; reporting results
368
369 (defstruct (time-info (:copier nil))
370   name
371   calls
372   seconds
373   consing)
374
375 ;;; Return our best guess for the run time in a function, subtracting
376 ;;; out factors for profiling overhead. We subtract out the internal
377 ;;; overhead for each call to this function, since the internal
378 ;;; overhead is the part of the profiling overhead for a function that
379 ;;; is charged to that function.
380 ;;;
381 ;;; We also subtract out a factor for each call to a profiled function
382 ;;; within this profiled function. This factor is the total profiling
383 ;;; overhead *minus the internal overhead*. We don't subtract out the
384 ;;; internal overhead, since it was already subtracted when the nested
385 ;;; profiled functions subtracted their running time from the time for
386 ;;; the enclosing function.
387 (defun compensate-time (calls ticks profile)
388   (let ((raw-compensated
389          (- (/ (float ticks) (float +ticks-per-second+))
390             (* (overhead-internal *overhead*) (float calls))
391             (* (- (overhead-total *overhead*)
392                   (overhead-internal *overhead*))
393                (float profile)))))
394     (max raw-compensated 0.0)))
395
396 (defun report ()
397   "Report results from profiling. The results are
398 approximately adjusted for profiling overhead, but when RAW is true
399 the unadjusted results are reported. The compensation may be somewhat
400 inaccurate when bignums are involved in runtime calculation, as in
401 a very-long-running Lisp process."
402   (declare (optimize (speed 0)))
403   (unless (boundp '*overhead*)
404     (setf *overhead*
405           (compute-overhead)))
406   (let ((time-info-list ())
407         (no-call-name-list ()))
408     (dohash (name pinfo *profiled-function-name->info*)
409       (unless (eq (fdefinition name)
410                   (profile-info-encapsulation-fun pinfo))
411         (warn "Function ~S has been redefined, so times may be inaccurate.~@
412                PROFILE it again to record calls to the new definition."
413               name))
414       (multiple-value-bind (calls ticks consing profile)
415           (funcall (profile-info-read-stats-fun pinfo))
416         (if (zerop calls)
417             (push name no-call-name-list)
418             (push (make-time-info :name name
419                                   :calls calls
420                                   :seconds (compensate-time calls
421                                                             ticks
422                                                             profile)
423                                   :consing consing)
424                   time-info-list))))
425
426     (setf time-info-list
427           (sort time-info-list
428                 #'>=
429                 :key #'time-info-seconds))
430
431     (format *trace-output*
432             "~&  seconds  |  consed   |  calls  |  sec/call  |  name~@
433                ------------------------------------------------------~%")
434
435     (let ((total-time 0.0)
436           (total-consed 0)
437           (total-calls 0))
438       (dolist (time-info time-info-list)
439         (incf total-time (time-info-seconds time-info))
440         (incf total-calls (time-info-calls time-info))
441         (incf total-consed (time-info-consing time-info))
442         (format *trace-output*
443                 "~10,3F | ~9:D | ~7:D | ~10,6F | ~S~%"
444                 (time-info-seconds time-info)
445                 (time-info-consing time-info)
446                 (time-info-calls time-info)
447                 (/ (time-info-seconds time-info)
448                    (float (time-info-calls time-info)))
449                 (time-info-name time-info)))
450       (format *trace-output*
451               "------------------------------------------------------~@
452               ~10,3F | ~9:D | ~7:D |        | Total~%"
453               total-time total-consed total-calls)
454       (format *trace-output*
455               "~%estimated total profiling overhead: ~4,2F seconds~%"
456               (* (overhead-total *overhead*) (float total-calls)))
457       (format *trace-output*
458               "~&overhead estimation parameters:~%  ~Ss/call, ~Ss total profiling, ~Ss internal profiling~%"
459               (overhead-call *overhead*)
460               (overhead-total *overhead*)
461               (overhead-internal *overhead*)))
462
463     (when no-call-name-list
464       (format *trace-output*
465               "~%These functions were not called:~%~{~<~%~:; ~S~>~}~%"
466               (sort no-call-name-list #'string<
467                     :key (lambda (name)
468                            (symbol-name (function-name-block-name name))))))
469
470     (values)))
471 \f
472 ;;;; overhead estimation
473
474 ;;; We average the timing overhead over this many iterations.
475 (defconstant +timer-overhead-iterations+ 50000)
476
477 ;;; a dummy function that we profile to find profiling overhead
478 (declaim (notinline compute-overhead-aux))
479 (defun compute-overhead-aux (x)
480   (declare (ignore x)))
481
482 ;;; Return a newly computed OVERHEAD object.
483 (defun compute-overhead ()
484   (flet ((frob ()
485            (let ((start (get-internal-ticks))
486                  (fun (symbol-function 'compute-overhead-aux)))
487              (dotimes (i +timer-overhead-iterations+)
488                (funcall fun fun))
489              (/ (float (- (get-internal-ticks) start))
490                 (float +ticks-per-second+)
491                 (float +timer-overhead-iterations+)))))
492     (let (;; Measure unprofiled calls to estimate call overhead.
493           (call-overhead (frob))
494           total-overhead
495           internal-overhead)
496       ;; Measure profiled calls to estimate profiling overhead.
497       (unwind-protect
498           (progn
499             (profile compute-overhead-aux)
500             (setf total-overhead
501                   (- (frob) call-overhead)))
502         (let* ((pinfo (gethash 'compute-overhead-aux
503                                *profiled-function-name->info*))
504                (read-stats-fun (profile-info-read-stats-fun pinfo))
505                (time (nth-value 1 (funcall read-stats-fun))))
506           (setf internal-overhead
507                 (/ (float time)
508                    (float +ticks-per-second+)
509                    (float +timer-overhead-iterations+))))
510         (unprofile compute-overhead-aux))
511       (make-overhead :call call-overhead
512                      :total total-overhead
513                      :internal internal-overhead))))
514
515 ;;; It would be bad to compute *OVERHEAD*, save it into a .core file,
516 ;;; then load old *OVERHEAD* value from the .core file into a
517 ;;; different machine running at a different speed. We avoid this by
518 ;;; erasing *CALL-OVERHEAD* whenever we save a .core file.
519 (pushnew (lambda ()
520            (makunbound '*overhead*))
521          *before-save-initializations*)