Initial revision
[sbcl.git] / src / code / debug.lisp
1 ;;;; the debugger
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")
13
14 (file-comment
15   "$Header$")
16 \f
17 ;;;; variables and constants
18
19 (defvar *debug-print-level* 3
20   #!+sb-doc
21   "*PRINT-LEVEL* for the debugger")
22
23 (defvar *debug-print-length* 5
24   #!+sb-doc
25   "*PRINT-LENGTH* for the debugger")
26
27 (defvar *debug-readtable*
28   ;; KLUDGE: This can't be initialized in a cold toplevel form, because the
29   ;; *STANDARD-READTABLE* isn't initialized until after cold toplevel forms
30   ;; have run. So instead we initialize it immediately after
31   ;; *STANDARD-READTABLE*. -- WHN 20000205
32   nil
33   #!+sb-doc
34   "*READTABLE* for the debugger")
35
36 (defvar *in-the-debugger* nil
37   #!+sb-doc
38   "This is T while in the debugger.")
39
40 (defvar *debug-command-level* 0
41   #!+sb-doc
42   "Pushes and pops/exits inside the debugger change this.")
43
44 (defvar *stack-top-hint* nil
45   #!+sb-doc
46   "If this is bound before the debugger is invoked, it is used as the stack
47    top by the debugger.")
48 (defvar *stack-top* nil)
49 (defvar *real-stack-top* nil)
50
51 (defvar *current-frame* nil)
52
53 ;;; the default for *DEBUG-PROMPT*
54 (defun debug-prompt ()
55   (let ((*standard-output* *debug-io*))
56     (terpri)
57     (prin1 (sb!di:frame-number *current-frame*))
58     (dotimes (i *debug-command-level*) (princ "]"))
59     (princ " ")
60     (force-output)))
61
62 (defparameter *debug-prompt* #'debug-prompt
63   #!+sb-doc
64   "a function of no arguments that prints the debugger prompt on *DEBUG-IO*")
65
66 (defparameter *debug-help-string*
67 "The prompt is right square brackets, the number indicating how many
68   recursive command loops you are in. 
69 Any command may be uniquely abbreviated.
70 The debugger rebinds various special variables for controlling i/o,
71   sometimes to defaults (a la WITH-STANDARD-IO-SYNTAX) and sometimes to 
72   its own values, e.g. SB-DEBUG:*DEBUG-PRINT-LEVEL*.
73 Debug commands do not affect * and friends, but evaluation in the debug loop
74   do affect these variables.
75 SB-DEBUG:*FLUSH-DEBUG-ERRORS* controls whether errors at the debug prompt
76   drop you into deeper into the debugger.
77
78 Getting in and out of the debugger:
79   Q        throws to top level.
80   GO       calls CONTINUE which tries to proceed with the restart 'CONTINUE.
81   RESTART  invokes restart numbered as shown (prompt if not given).
82   ERROR    prints the error condition and restart cases.
83
84   The name of any restart, or its number, is a valid command, and is the same
85     as using RESTART to invoke that restart.
86
87 Changing frames:
88   U     up frame     D  down frame
89   T     top frame    B  bottom frame
90   F n   frame n
91
92 Inspecting frames:
93   BACKTRACE [n]  shows n frames going down the stack.
94   LIST-LOCALS, L lists locals in current function.
95   PRINT, P       displays current function call.
96   SOURCE [n]     displays frame's source form with n levels of enclosing forms.
97
98 Breakpoints and steps:
99   LIST-LOCATIONS [{function | :c}]   List the locations for breakpoints.
100                                      Specify :c for the current frame.
101     Abbreviation: LL
102   LIST-BREAKPOINTS                   List the active breakpoints.
103     Abbreviations: LB, LBP
104   DELETE-BREAKPOINT [n]              Remove breakpoint n or all breakpoints.
105     Abbreviations: DEL, DBP
106   BREAKPOINT {n | :end | :start} [:break form] [:function function]
107              [{:print form}*] [:condition form]
108                                      Set a breakpoint.
109     Abbreviations: BR, BP
110   STEP [n]                           Step to the next location or step n times.
111
112 Function and macro commands:
113  (SB-DEBUG:DEBUG-RETURN expression)
114     Exit the debugger, returning expression's values from the current frame.
115  (SB-DEBUG:ARG n)
116     Return the n'th argument in the current frame.
117  (SB-DEBUG:VAR string-or-symbol [id])
118     Returns the value of the specified variable in the current frame.")
119 \f
120 ;;; This is used to communicate to DEBUG-LOOP that we are at a step breakpoint.
121 (define-condition step-condition (simple-condition) ())
122 \f
123 ;;;; breakpoint state
124
125 (defvar *only-block-start-locations* nil
126   #!+sb-doc
127   "When true, the LIST-LOCATIONS command only displays block start locations.
128    Otherwise, all locations are displayed.")
129
130 (defvar *print-location-kind* nil
131   #!+sb-doc
132   "When true, list the code location type in the LIST-LOCATIONS command.")
133
134 ;;; a list of the types of code-locations that should not be stepped to and
135 ;;; should not be listed when listing breakpoints
136 (defvar *bad-code-location-types* '(:call-site :internal-error))
137 (declaim (type list *bad-code-location-types*))
138
139 ;;; code locations of the possible breakpoints
140 (defvar *possible-breakpoints*)
141 (declaim (type list *possible-breakpoints*))
142
143 ;;; a list of the made and active breakpoints, each is a breakpoint-info
144 ;;; structure
145 (defvar *breakpoints* nil)
146 (declaim (type list *breakpoints*))
147
148 ;;; a list of breakpoint-info structures of the made and active step
149 ;;; breakpoints
150 (defvar *step-breakpoints* nil)
151 (declaim (type list *step-breakpoints*))
152
153 ;;; the number of times left to step
154 (defvar *number-of-steps* 1)
155 (declaim (type integer *number-of-steps*))
156
157 ;;; This is used when listing and setting breakpoints.
158 (defvar *default-breakpoint-debug-function* nil)
159 (declaim (type (or list sb!di:debug-function) *default-breakpoint-debug-function*))
160 \f
161 ;;;; code location utilities
162
163 ;;; Return the first code-location in the passed debug block.
164 (defun first-code-location (debug-block)
165   (let ((found nil)
166         (first-code-location nil))
167     (sb!di:do-debug-block-locations (code-location debug-block)
168       (unless found
169         (setf first-code-location code-location)
170         (setf found t)))
171     first-code-location))
172
173 ;;; Return a list of the next code-locations following the one passed. One of
174 ;;; the *BAD-CODE-LOCATION-TYPES* will not be returned.
175 (defun next-code-locations (code-location)
176   (let ((debug-block (sb!di:code-location-debug-block code-location))
177         (block-code-locations nil))
178     (sb!di:do-debug-block-locations (block-code-location debug-block)
179       (unless (member (sb!di:code-location-kind block-code-location)
180                       *bad-code-location-types*)
181         (push block-code-location block-code-locations)))
182     (setf block-code-locations (nreverse block-code-locations))
183     (let* ((code-loc-list (rest (member code-location block-code-locations
184                                         :test #'sb!di:code-location=)))
185            (next-list (cond (code-loc-list
186                              (list (first code-loc-list)))
187                             ((map 'list #'first-code-location
188                                   (sb!di:debug-block-successors debug-block)))
189                             (t nil))))
190       (when (and (= (length next-list) 1)
191                  (sb!di:code-location= (first next-list) code-location))
192         (setf next-list (next-code-locations (first next-list))))
193       next-list)))
194
195 ;;; Returns a list of code-locations of the possible breakpoints of the
196 ;;; debug-function passed.
197 (defun possible-breakpoints (debug-function)
198   (let ((possible-breakpoints nil))
199     (sb!di:do-debug-function-blocks (debug-block debug-function)
200       (unless (sb!di:debug-block-elsewhere-p debug-block)
201         (if *only-block-start-locations*
202             (push (first-code-location debug-block) possible-breakpoints)
203             (sb!di:do-debug-block-locations (code-location debug-block)
204               (when (not (member (sb!di:code-location-kind code-location)
205                                  *bad-code-location-types*))
206                 (push code-location possible-breakpoints))))))
207     (nreverse possible-breakpoints)))
208
209 ;;; Searches the info-list for the item passed (code-location, debug-function,
210 ;;; or breakpoint-info). If the item passed is a debug function then kind will
211 ;;; be compared if it was specified. The kind if also compared if a
212 ;;; breakpoint-info is passed since it's in the breakpoint. The info structure
213 ;;; is returned if found.
214 (defun location-in-list (place info-list &optional (kind nil))
215   (when (breakpoint-info-p place)
216     (setf kind (sb!di:breakpoint-kind (breakpoint-info-breakpoint place)))
217     (setf place (breakpoint-info-place place)))
218   (cond ((sb!di:code-location-p place)
219          (find place info-list
220                :key #'breakpoint-info-place
221                :test #'(lambda (x y) (and (sb!di:code-location-p y)
222                                           (sb!di:code-location= x y)))))
223         (t
224          (find place info-list
225                :test #'(lambda (x-debug-function y-info)
226                          (let ((y-place (breakpoint-info-place y-info))
227                                (y-breakpoint (breakpoint-info-breakpoint
228                                               y-info)))
229                            (and (sb!di:debug-function-p y-place)
230                                 (eq x-debug-function y-place)
231                                 (or (not kind)
232                                     (eq kind (sb!di:breakpoint-kind
233                                               y-breakpoint))))))))))
234
235 ;;; If Loc is an unknown location, then try to find the block start location.
236 ;;; Used by source printing to some information instead of none for the user.
237 (defun maybe-block-start-location (loc)
238   (if (sb!di:code-location-unknown-p loc)
239       (let* ((block (sb!di:code-location-debug-block loc))
240              (start (sb!di:do-debug-block-locations (loc block)
241                       (return loc))))
242         (cond ((and (not (sb!di:debug-block-elsewhere-p block))
243                     start)
244                ;; FIXME: Why output on T instead of *DEBUG-FOO* or something?
245                (format t "~%unknown location: using block start~%")
246                start)
247               (t
248                loc)))
249       loc))
250 \f
251 ;;;; the BREAKPOINT-INFO structure
252
253 ;;; info about a made breakpoint
254 (defstruct breakpoint-info
255   ;; where we are going to stop
256   (place (required-argument)
257          :type (or sb!di:code-location sb!di:debug-function))
258   ;; the breakpoint returned by sb!di:make-breakpoint
259   (breakpoint (required-argument) :type sb!di:breakpoint)
260   ;; the function returned from sb!di:preprocess-for-eval. If result is
261   ;; non-NIL, drop into the debugger.
262   (break #'identity :type function)
263   ;; the function returned from sb!di:preprocess-for-eval. If result is
264   ;; non-NIL, eval (each) print and print results.
265   (condition #'identity :type function)
266   ;; the list of functions from sb!di:preprocess-for-eval to evaluate. Results
267   ;; are conditionally printed. Car of each element is the function, cdr is the
268   ;; form it goes with.
269   (print nil :type list)
270   ;; the number used when listing the possible breakpoints within a function.
271   ;; Could also be a symbol such as start or end.
272   (code-location-number (required-argument) :type (or symbol integer))
273   ;; the number used when listing the breakpoints active and to delete
274   ;; breakpoints
275   (breakpoint-number (required-argument) :type integer))
276
277 ;;; Return a new BREAKPOINT-INFO structure with the info passed.
278 (defun create-breakpoint-info (place breakpoint code-location-number
279                                      &key (break #'identity)
280                                      (condition #'identity) (print nil))
281   (setf *breakpoints*
282         (sort *breakpoints* #'< :key #'breakpoint-info-breakpoint-number))
283   (let ((breakpoint-number
284          (do ((i 1 (incf i)) (breakpoints *breakpoints* (rest breakpoints)))
285              ((or (> i (length *breakpoints*))
286                   (not (= i (breakpoint-info-breakpoint-number
287                              (first breakpoints)))))
288
289               i))))
290     (make-breakpoint-info :place place :breakpoint breakpoint
291                           :code-location-number code-location-number
292                           :breakpoint-number breakpoint-number
293                           :break break :condition condition :print print)))
294
295 ;;; Print the breakpoint info for the breakpoint-info structure passed.
296 (defun print-breakpoint-info (breakpoint-info)
297   (let ((place (breakpoint-info-place breakpoint-info))
298         (bp-number (breakpoint-info-breakpoint-number breakpoint-info))
299         (loc-number (breakpoint-info-code-location-number breakpoint-info)))
300     (case (sb!di:breakpoint-kind (breakpoint-info-breakpoint breakpoint-info))
301       (:code-location
302        (print-code-location-source-form place 0)
303        (format t
304                "~&~S: ~S in ~S"
305                bp-number
306                loc-number
307                (sb!di:debug-function-name (sb!di:code-location-debug-function
308                                            place))))
309       (:function-start
310        (format t "~&~S: FUNCTION-START in ~S" bp-number
311                (sb!di:debug-function-name place)))
312       (:function-end
313        (format t "~&~S: FUNCTION-END in ~S" bp-number
314                (sb!di:debug-function-name place))))))
315 \f
316 ;;;; MAIN-HOOK-FUNCTION for steps and breakpoints
317
318 ;;; This must be passed as the hook function. It keeps track of where step
319 ;;; breakpoints are.
320 (defun main-hook-function (current-frame breakpoint &optional return-vals
321                                          function-end-cookie)
322   (setf *default-breakpoint-debug-function*
323         (sb!di:frame-debug-function current-frame))
324   (dolist (step-info *step-breakpoints*)
325     (sb!di:delete-breakpoint (breakpoint-info-breakpoint step-info))
326     (let ((bp-info (location-in-list step-info *breakpoints*)))
327       (when bp-info
328         (sb!di:activate-breakpoint (breakpoint-info-breakpoint bp-info)))))
329   (let ((*stack-top-hint* current-frame)
330         (step-hit-info
331          (location-in-list (sb!di:breakpoint-what breakpoint)
332                            *step-breakpoints*
333                            (sb!di:breakpoint-kind breakpoint)))
334         (bp-hit-info
335          (location-in-list (sb!di:breakpoint-what breakpoint)
336                            *breakpoints*
337                            (sb!di:breakpoint-kind breakpoint)))
338         (break)
339         (condition)
340         (string ""))
341     (setf *step-breakpoints* nil)
342     (labels ((build-string (str)
343                (setf string (concatenate 'string string str)))
344              (print-common-info ()
345                (build-string
346                 (with-output-to-string (*standard-output*)
347                   (when function-end-cookie
348                     (format t "~%Return values: ~S" return-vals))
349                   (when condition
350                     (when (breakpoint-info-print bp-hit-info)
351                       (format t "~%")
352                       (print-frame-call current-frame))
353                     (dolist (print (breakpoint-info-print bp-hit-info))
354                       (format t "~& ~S = ~S" (rest print)
355                               (funcall (first print) current-frame))))))))
356       (when bp-hit-info
357         (setf break (funcall (breakpoint-info-break bp-hit-info)
358                              current-frame))
359         (setf condition (funcall (breakpoint-info-condition bp-hit-info)
360                                  current-frame)))
361       (cond ((and bp-hit-info step-hit-info (= 1 *number-of-steps*))
362              (build-string (format nil "~&*Step (to a breakpoint)*"))
363              (print-common-info)
364              (break string))
365             ((and bp-hit-info step-hit-info break)
366              (build-string (format nil "~&*Step (to a breakpoint)*"))
367              (print-common-info)
368              (break string))
369             ((and bp-hit-info step-hit-info)
370              (print-common-info)
371              (format t "~A" string)
372              (decf *number-of-steps*)
373              (set-step-breakpoint current-frame))
374             ((and step-hit-info (= 1 *number-of-steps*))
375              (build-string "*Step*")
376              (break (make-condition 'step-condition :format-control string)))
377             (step-hit-info
378              (decf *number-of-steps*)
379              (set-step-breakpoint current-frame))
380             (bp-hit-info
381              (when break
382                (build-string (format nil "~&*Breakpoint hit*")))
383              (print-common-info)
384              (if break
385                  (break string)
386                  (format t "~A" string)))
387             (t
388              (break "error in main-hook-function: unknown breakpoint"))))))
389 \f
390 ;;; Set breakpoints at the next possible code-locations. After calling
391 ;;; this, either (CONTINUE) if in the debugger or just let program flow
392 ;;; return if in a hook function.
393 (defun set-step-breakpoint (frame)
394   (cond
395    ((sb!di:debug-block-elsewhere-p (sb!di:code-location-debug-block
396                                     (sb!di:frame-code-location frame)))
397     ;; FIXME: FORMAT T is used for error output here and elsewhere in
398     ;; the debug code.
399     (format t "cannot step, in elsewhere code~%"))
400    (t
401     (let* ((code-location (sb!di:frame-code-location frame))
402            (next-code-locations (next-code-locations code-location)))
403       (cond
404        (next-code-locations
405         (dolist (code-location next-code-locations)
406           (let ((bp-info (location-in-list code-location *breakpoints*)))
407             (when bp-info
408               (sb!di:deactivate-breakpoint (breakpoint-info-breakpoint
409                                             bp-info))))
410           (let ((bp (sb!di:make-breakpoint #'main-hook-function code-location
411                                            :kind :code-location)))
412             (sb!di:activate-breakpoint bp)
413             (push (create-breakpoint-info code-location bp 0)
414                   *step-breakpoints*))))
415        (t
416         (let* ((debug-function (sb!di:frame-debug-function *current-frame*))
417                (bp (sb!di:make-breakpoint #'main-hook-function debug-function
418                                           :kind :function-end)))
419           (sb!di:activate-breakpoint bp)
420           (push (create-breakpoint-info debug-function bp 0)
421                 *step-breakpoints*))))))))
422 \f
423 ;;;; STEP
424
425 ;;; ANSI specifies that this macro shall exist, even if only as a
426 ;;; trivial placeholder like this.
427 (defmacro step (form)
428   "a trivial placeholder implementation of the CL:STEP macro required by
429    the ANSI spec"
430   `(progn
431      ,form))
432 \f
433 ;;;; BACKTRACE
434
435 (defun backtrace (&optional (count most-positive-fixnum)
436                             (*standard-output* *debug-io*))
437   #!+sb-doc
438   "Show a listing of the call stack going down from the current frame. In the
439    debugger, the current frame is indicated by the prompt. Count is how many
440    frames to show."
441   (fresh-line *standard-output*)
442   (do ((frame (if *in-the-debugger* *current-frame* (sb!di:top-frame))
443               (sb!di:frame-down frame))
444        (count count (1- count)))
445       ((or (null frame) (zerop count)))
446     (print-frame-call frame :number t))
447   (fresh-line *standard-output*)
448   (values))
449 \f
450 ;;;; frame printing
451
452 (eval-when (:compile-toplevel :execute)
453
454 ;;; This is a convenient way to express what to do for each type of lambda-list
455 ;;; element.
456 (sb!xc:defmacro lambda-list-element-dispatch (element
457                                               &key
458                                               required
459                                               optional
460                                               rest
461                                               keyword
462                                               deleted)
463   `(etypecase ,element
464      (sb!di:debug-var
465       ,@required)
466      (cons
467       (ecase (car ,element)
468         (:optional ,@optional)
469         (:rest ,@rest)
470         (:keyword ,@keyword)))
471      (symbol
472       (assert (eq ,element :deleted))
473       ,@deleted)))
474
475 (sb!xc:defmacro lambda-var-dispatch (variable location deleted valid other)
476   (let ((var (gensym)))
477     `(let ((,var ,variable))
478        (cond ((eq ,var :deleted) ,deleted)
479              ((eq (sb!di:debug-var-validity ,var ,location) :valid)
480               ,valid)
481              (t ,other)))))
482
483 ) ; EVAL-WHEN
484
485 ;;; This is used in constructing arg lists for debugger printing when
486 ;;; the arg list is unavailable, some arg is unavailable or unused,
487 ;;; etc.
488 (defstruct (unprintable-object
489             (:constructor make-unprintable-object (string))
490             (:print-object (lambda (x s)
491                              (print-unreadable-object (x s :type t)
492                                (write-string (unprintable-object-string x)
493                                              s)))))
494   string)
495
496 ;;; Print frame with verbosity level 1. If we hit a rest-arg, then
497 ;;; print as many of the values as possible, punting the loop over
498 ;;; lambda-list variables since any other arguments will be in the
499 ;;; rest-arg's list of values.
500 (defun print-frame-call-1 (frame)
501   (let* ((d-fun (sb!di:frame-debug-function frame))
502          (loc (sb!di:frame-code-location frame))
503          (results (list (sb!di:debug-function-name d-fun))))
504     (handler-case
505         (dolist (ele (sb!di:debug-function-lambda-list d-fun))
506           (lambda-list-element-dispatch ele
507             :required ((push (frame-call-arg ele loc frame) results))
508             :optional ((push (frame-call-arg (second ele) loc frame) results))
509             :keyword ((push (second ele) results)
510                       (push (frame-call-arg (third ele) loc frame) results))
511             :deleted ((push (frame-call-arg ele loc frame) results))
512             :rest ((lambda-var-dispatch (second ele) loc
513                      nil
514                      (progn
515                        (setf results
516                              (append (reverse (sb!di:debug-var-value
517                                                (second ele) frame))
518                                      results))
519                        (return))
520                      (push (make-unprintable-object "unavailable &REST arg")
521                            results)))))
522       (sb!di:lambda-list-unavailable
523        ()
524        (push (make-unprintable-object "lambda list unavailable") results)))
525     (prin1 (mapcar #'ensure-printable-object (nreverse results)))
526     (when (sb!di:debug-function-kind d-fun)
527       (write-char #\[)
528       (prin1 (sb!di:debug-function-kind d-fun))
529       (write-char #\]))))
530
531 (defun ensure-printable-object (object)
532   (handler-case
533       (with-open-stream (out (make-broadcast-stream))
534         (prin1 object out)
535         object)
536     (error (cond)
537       (declare (ignore cond))
538       (make-unprintable-object "error printing object"))))
539
540 (defun frame-call-arg (var location frame)
541   (lambda-var-dispatch var location
542     (make-unprintable-object "unused arg")
543     (sb!di:debug-var-value var frame)
544     (make-unprintable-object "unavailable arg")))
545
546 ;;; Prints a representation of the function call causing frame to
547 ;;; exist. Verbosity indicates the level of information to output;
548 ;;; zero indicates just printing the debug-function's name, and one
549 ;;; indicates displaying call-like, one-liner format with argument
550 ;;; values.
551 (defun print-frame-call (frame &key (verbosity 1) (number nil))
552   (cond
553    ((zerop verbosity)
554     (when number
555       (format t "~&~S: " (sb!di:frame-number frame)))
556     (format t "~S" frame))
557    (t
558     (when number
559       (format t "~&~S: " (sb!di:frame-number frame)))
560     (print-frame-call-1 frame)))
561   (when (>= verbosity 2)
562     (let ((loc (sb!di:frame-code-location frame)))
563       (handler-case
564           (progn
565             (sb!di:code-location-debug-block loc)
566             (format t "~%source: ")
567             (print-code-location-source-form loc 0))
568         (sb!di:debug-condition (ignore) ignore)
569         (error (c) (format t "error finding source: ~A" c))))))
570 \f
571 ;;;; INVOKE-DEBUGGER
572
573 (defvar *debugger-hook* nil
574   #!+sb-doc
575   "This is either NIL or a function of two arguments, a condition and the value
576    of *DEBUGGER-HOOK*. This function can either handle the condition or return
577    which causes the standard debugger to execute. The system passes the value
578    of this variable to the function because it binds *DEBUGGER-HOOK* to NIL
579    around the invocation.")
580
581 ;;; These are bound on each invocation of INVOKE-DEBUGGER.
582 (defvar *debug-restarts*)
583 (defvar *debug-condition*)
584
585 (defun invoke-debugger (condition)
586   #!+sb-doc
587   "Enter the debugger."
588   (let ((old-hook *debugger-hook*))
589     (when old-hook
590       (let ((*debugger-hook* nil))
591         (funcall hook condition hook))))
592   (sb!unix:unix-sigsetmask 0)
593   (let ((original-package *package*)) ; protect it from WITH-STANDARD-IO-SYNTAX
594     (with-standard-io-syntax
595      (let* ((*debug-condition* condition)
596             (*debug-restarts* (compute-restarts condition))
597             ;; FIXME: The next two bindings seem flaky, violating the
598             ;; principle of least surprise. But in order to fix them, we'd
599             ;; need to go through all the i/o statements in the debugger,
600             ;; since a lot of them do their thing on *STANDARD-INPUT* and
601             ;; *STANDARD-OUTPUT* instead of *DEBUG-IO*.
602             (*standard-input* *debug-io*) ; in case of setq
603             (*standard-output* *debug-io*) ; ''  ''  ''  ''
604             ;; We also want to set the i/o subsystem into a known, useful 
605             ;; state, regardless of where in the debugger was invoked in the 
606             ;; program. WITH-STANDARD-IO-SYNTAX does some of that, but
607             ;;   1. It doesn't affect our internal special variables like
608             ;;      *CURRENT-LEVEL*.
609             ;;   2. It isn't customizable.
610             ;;   3. It doesn't set *PRINT-READABLY* or *PRINT-PRETTY* to the
611             ;;      same value as the toplevel default.
612             ;;   4. It sets *PACKAGE* to COMMON-LISP-USER, which is not
613             ;;      helpful behavior for a debugger.
614             ;; We try to remedy all these problems with explicit rebindings
615             ;; here.
616             (sb!kernel:*current-level* 0)
617             (*print-length* *debug-print-length*)
618             (*print-level* *debug-print-level*)
619             (*readtable* *debug-readtable*)
620             (*print-readably* nil)
621             (*print-pretty* t)
622             (*package* original-package))
623        (format *error-output*
624                "~2&debugger invoked on ~S of type ~S:~%  ~A~%"
625                '*debug-condition*
626                (type-of *debug-condition*)
627                *debug-condition*)
628        (let (;; FIXME: like the bindings of *STANDARD-INPUT* and
629              ;; *STANDARD-OUTPUT* above..
630              (*error-output* *debug-io*))
631          (unless (typep condition 'step-condition)
632            (show-restarts *debug-restarts* *error-output*))
633          (internal-debug))))))
634
635 (defun show-restarts (restarts &optional (s *error-output*))
636   (when restarts
637     (format s "~&restarts:~%")
638     (let ((count 0)
639           (names-used '(nil))
640           (max-name-len 0))
641       (dolist (restart restarts)
642         (let ((name (restart-name restart)))
643           (when name
644             (let ((len (length (princ-to-string name))))
645               (when (> len max-name-len)
646                 (setf max-name-len len))))))
647       (unless (zerop max-name-len)
648         (incf max-name-len 3))
649       (dolist (restart restarts)
650         (let ((name (restart-name restart)))
651           (cond ((member name names-used)
652                  (format s "~& ~2D: ~@VT~A~%" count max-name-len restart))
653                 (t
654                  (format s "~& ~2D: [~VA] ~A~%"
655                          count (- max-name-len 3) name restart)
656                  (push name names-used))))
657         (incf count)))))
658
659 ;;; This calls DEBUG-LOOP, performing some simple initializations before doing
660 ;;; so. INVOKE-DEBUGGER calls this to actually get into the debugger.
661 ;;; SB!CONDITIONS::ERROR-ERROR calls this in emergencies to get into a debug
662 ;;; prompt as quickly as possible with as little risk as possible for stepping
663 ;;; on whatever is causing recursive errors.
664 (defun internal-debug ()
665   (let ((*in-the-debugger* t)
666         (*read-suppress* nil))
667     (unless (typep *debug-condition* 'step-condition)
668       (clear-input *debug-io*)
669       (format *debug-io*
670               "~&Within the debugger, you can type HELP for help.~%"))
671     #!-mp (debug-loop)
672     #!+mp (sb!mp:without-scheduling (debug-loop))))
673 \f
674 ;;;; DEBUG-LOOP
675
676 ;;; Note: This defaulted to T in CMU CL. The changed default in SBCL
677 ;;; was motivated by desire to play nicely with ILISP.
678 (defvar *flush-debug-errors* nil
679   #!+sb-doc
680   "When set, avoid calling INVOKE-DEBUGGER recursively when errors occur while
681    executing in the debugger.")
682
683 (defun debug-loop ()
684   (let* ((*debug-command-level* (1+ *debug-command-level*))
685          (*real-stack-top* (sb!di:top-frame))
686          (*stack-top* (or *stack-top-hint* *real-stack-top*))
687          (*stack-top-hint* nil)
688          (*current-frame* *stack-top*))
689     (handler-bind ((sb!di:debug-condition (lambda (condition)
690                                             (princ condition *debug-io*)
691                                             (throw 'debug-loop-catcher nil))))
692       (fresh-line)
693       (print-frame-call *current-frame* :verbosity 2)
694       (loop
695         (catch 'debug-loop-catcher
696           (handler-bind ((error #'(lambda (condition)
697                                     (when *flush-debug-errors*
698                                       (clear-input *debug-io*)
699                                       (princ condition)
700                                       ;; FIXME: Doing input on *DEBUG-IO*
701                                       ;; and output on T seems broken.
702                                       (format t
703                                               "~&error flushed (because ~
704                                                ~S is set)"
705                                               '*flush-debug-errors*)
706                                       (throw 'debug-loop-catcher nil)))))
707             ;; We have to bind level for the restart function created by
708             ;; WITH-SIMPLE-RESTART.
709             (let ((level *debug-command-level*)
710                   (restart-commands (make-restart-commands)))
711               (with-simple-restart (abort "Return to debug level ~D." level)
712                 (funcall *debug-prompt*)
713                 (let ((input (sb!int:get-stream-command *debug-io*)))
714                   (cond (input
715                          (let ((cmd-fun (debug-command-p
716                                          (sb!int:stream-command-name input)
717                                          restart-commands)))
718                            (cond
719                             ((not cmd-fun)
720                              (error "unknown stream-command: ~S" input))
721                             ((consp cmd-fun)
722                              (error "ambiguous debugger command: ~S" cmd-fun))
723                             (t
724                              (apply cmd-fun
725                                     (sb!int:stream-command-args input))))))
726                         (t
727                          (let* ((exp (read))
728                                 (cmd-fun (debug-command-p exp
729                                                           restart-commands)))
730                            (cond ((not cmd-fun)
731                                   (debug-eval-print exp))
732                                  ((consp cmd-fun)
733                                   (format t
734                                           "~&Your command, ~S, is ambiguous:~%"
735                                           exp)
736                                   (dolist (ele cmd-fun)
737                                     (format t "   ~A~%" ele)))
738                                  (t
739                                   (funcall cmd-fun)))))))))))))))
740
741 (defvar *auto-eval-in-frame* t
742   #!+sb-doc
743   "When set (the default), evaluations in the debugger's command loop occur
744    relative to the current frame's environment without the need of debugger
745    forms that explicitly control this kind of evaluation.")
746
747 ;;; FIXME: We could probably use INTERACTIVE-EVAL for much of this logic.
748 (defun debug-eval-print (exp)
749   (setq +++ ++ ++ + + - - exp)
750   (let* ((values (multiple-value-list
751                   (if (and (fboundp 'compile) *auto-eval-in-frame*)
752                       (sb!di:eval-in-frame *current-frame* -)
753                       (eval -))))
754          (*standard-output* *debug-io*))
755     (fresh-line)
756     (if values (prin1 (car values)))
757     (dolist (x (cdr values))
758       (fresh-line)
759       (prin1 x))
760     (setq /// // // / / values)
761     (setq *** ** ** * * (car values))
762     ;; Make sure that nobody passes back an unbound marker.
763     (unless (boundp '*)
764       (setq * nil)
765       (fresh-line)
766       ;; FIXME: Perhaps this shouldn't be WARN (for fear of complicating
767       ;; the debugging situation?) but at least it should go to *ERROR-OUTPUT*.
768       ;; (And probably it should just be WARN.)
769       (princ "Setting * to NIL (was unbound marker)."))))
770 \f
771 ;;;; debug loop functions
772
773 ;;; These commands are functions, not really commands, so that users can get
774 ;;; their hands on the values returned.
775
776 (eval-when (:execute :compile-toplevel)
777
778 (sb!xc:defmacro define-var-operation (ref-or-set &optional value-var)
779   `(let* ((temp (etypecase name
780                   (symbol (sb!di:debug-function-symbol-variables
781                            (sb!di:frame-debug-function *current-frame*)
782                            name))
783                   (simple-string (sb!di:ambiguous-debug-vars
784                                   (sb!di:frame-debug-function *current-frame*)
785                                   name))))
786           (location (sb!di:frame-code-location *current-frame*))
787           ;; Let's only deal with valid variables.
788           (vars (remove-if-not #'(lambda (v)
789                                    (eq (sb!di:debug-var-validity v location)
790                                        :valid))
791                                temp)))
792      (declare (list vars))
793      (cond ((null vars)
794             (error "No known valid variables match ~S." name))
795            ((= (length vars) 1)
796             ,(ecase ref-or-set
797                (:ref
798                 '(sb!di:debug-var-value (car vars) *current-frame*))
799                (:set
800                 `(setf (sb!di:debug-var-value (car vars) *current-frame*)
801                        ,value-var))))
802            (t
803             ;; Since we have more than one, first see whether we have any
804             ;; variables that exactly match the specification.
805             (let* ((name (etypecase name
806                            (symbol (symbol-name name))
807                            (simple-string name)))
808                    ;; FIXME: REMOVE-IF-NOT is deprecated, use STRING/=
809                    ;; instead.
810                    (exact (remove-if-not (lambda (v)
811                                            (string= (sb!di:debug-var-symbol-name v)
812                                                     name))
813                                          vars))
814                    (vars (or exact vars)))
815               (declare (simple-string name)
816                        (list exact vars))
817               (cond
818                ;; Check now for only having one variable.
819                ((= (length vars) 1)
820                 ,(ecase ref-or-set
821                    (:ref
822                     '(sb!di:debug-var-value (car vars) *current-frame*))
823                    (:set
824                     `(setf (sb!di:debug-var-value (car vars) *current-frame*)
825                            ,value-var))))
826                ;; If there weren't any exact matches, flame about ambiguity
827                ;; unless all the variables have the same name.
828                ((and (not exact)
829                      (find-if-not
830                       #'(lambda (v)
831                           (string= (sb!di:debug-var-symbol-name v)
832                                    (sb!di:debug-var-symbol-name (car vars))))
833                       (cdr vars)))
834                 (error "specification ambiguous:~%~{   ~A~%~}"
835                        (mapcar #'sb!di:debug-var-symbol-name
836                                (delete-duplicates
837                                 vars :test #'string=
838                                 :key #'sb!di:debug-var-symbol-name))))
839                ;; All names are the same, so see whether the user ID'ed one of
840                ;; them.
841                (id-supplied
842                 (let ((v (find id vars :key #'sb!di:debug-var-id)))
843                   (unless v
844                     (error
845                      "invalid variable ID, ~D: should have been one of ~S"
846                      id
847                      (mapcar #'sb!di:debug-var-id vars)))
848                   ,(ecase ref-or-set
849                      (:ref
850                       '(sb!di:debug-var-value v *current-frame*))
851                      (:set
852                       `(setf (sb!di:debug-var-value v *current-frame*)
853                              ,value-var)))))
854                (t
855                 (error "Specify variable ID to disambiguate ~S. Use one of ~S."
856                        name
857                        (mapcar #'sb!di:debug-var-id vars)))))))))
858
859 ) ; EVAL-WHEN
860
861 (defun var (name &optional (id 0 id-supplied))
862   #!+sb-doc
863   "Returns a variable's value if possible. Name is a simple-string or symbol.
864    If it is a simple-string, it is an initial substring of the variable's name.
865    If name is a symbol, it has the same name and package as the variable whose
866    value this function returns. If the symbol is uninterned, then the variable
867    has the same name as the symbol, but it has no package.
868
869    If name is the initial substring of variables with different names, then
870    this return no values after displaying the ambiguous names. If name
871    determines multiple variables with the same name, then you must use the
872    optional id argument to specify which one you want. If you left id
873    unspecified, then this returns no values after displaying the distinguishing
874    id values.
875
876    The result of this function is limited to the availability of variable
877    information. This is SETF'able."
878   (define-var-operation :ref))
879 (defun (setf var) (value name &optional (id 0 id-supplied))
880   (define-var-operation :set value))
881
882 ;;; This returns the COUNT'th arg as the user sees it from args, the result of
883 ;;; SB!DI:DEBUG-FUNCTION-LAMBDA-LIST. If this returns a potential
884 ;;; DEBUG-VAR from the lambda-list, then the second value is T. If this
885 ;;; returns a keyword symbol or a value from a rest arg, then the second value
886 ;;; is NIL.
887 (declaim (ftype (function (index list)) nth-arg))
888 (defun nth-arg (count args)
889   (let ((n count))
890     (dolist (ele args (error "The argument specification ~S is out of range."
891                              n))
892       (lambda-list-element-dispatch ele
893         :required ((if (zerop n) (return (values ele t))))
894         :optional ((if (zerop n) (return (values (second ele) t))))
895         :keyword ((cond ((zerop n)
896                          (return (values (second ele) nil)))
897                         ((zerop (decf n))
898                          (return (values (third ele) t)))))
899         :deleted ((if (zerop n) (return (values ele t))))
900         :rest ((let ((var (second ele)))
901                  (lambda-var-dispatch var (sb!di:frame-code-location
902                                            *current-frame*)
903                    (error "unused REST-arg before n'th argument")
904                    (dolist (value
905                             (sb!di:debug-var-value var *current-frame*)
906                             (error
907                              "The argument specification ~S is out of range."
908                              n))
909                      (if (zerop n)
910                          (return-from nth-arg (values value nil))
911                          (decf n)))
912                    (error "invalid REST-arg before n'th argument")))))
913       (decf n))))
914
915 (defun arg (n)
916   #!+sb-doc
917   "Returns the N'th argument's value if possible. Argument zero is the first
918    argument in a frame's default printed representation. Count keyword/value
919    pairs as separate arguments."
920   (multiple-value-bind (var lambda-var-p)
921       (nth-arg n (handler-case (sb!di:debug-function-lambda-list
922                                 (sb!di:frame-debug-function *current-frame*))
923                    (sb!di:lambda-list-unavailable ()
924                      (error "No argument values are available."))))
925     (if lambda-var-p
926         (lambda-var-dispatch var (sb!di:frame-code-location *current-frame*)
927           (error "Unused arguments have no values.")
928           (sb!di:debug-var-value var *current-frame*)
929           (error "invalid argument value"))
930         var)))
931 \f
932 ;;;; machinery for definition of debug loop commands
933
934 (defvar *debug-commands* nil)
935
936 ;;; Interface to *DEBUG-COMMANDS*. No required arguments in args are
937 ;;; permitted.
938 ;;;
939 ;;; FIXME: This is not needed in the target Lisp system.
940 (defmacro def-debug-command (name args &rest body)
941   (let ((fun-name (intern (concatenate 'simple-string name "-DEBUG-COMMAND"))))
942     `(progn
943        (setf *debug-commands*
944              (remove ,name *debug-commands* :key #'car :test #'string=))
945        (defun ,fun-name ,args
946          (unless *in-the-debugger*
947            (error "invoking debugger command while outside the debugger"))
948          ,@body)
949        (push (cons ,name #',fun-name) *debug-commands*)
950        ',fun-name)))
951
952 (defun def-debug-command-alias (new-name existing-name)
953   (let ((pair (assoc existing-name *debug-commands* :test #'string=)))
954     (unless pair (error "unknown debug command name: ~S" existing-name))
955     (push (cons new-name (cdr pair)) *debug-commands*))
956   new-name)
957
958 ;;; This takes a symbol and uses its name to find a debugger command, using
959 ;;; initial substring matching. It returns the command function if form
960 ;;; identifies only one command, but if form is ambiguous, this returns a list
961 ;;; of the command names. If there are no matches, this returns nil. Whenever
962 ;;; the loop that looks for a set of possibilities encounters an exact name
963 ;;; match, we return that command function immediately.
964 (defun debug-command-p (form &optional other-commands)
965   (if (or (symbolp form) (integerp form))
966       (let* ((name
967               (if (symbolp form)
968                   (symbol-name form)
969                   (format nil "~D" form)))
970              (len (length name))
971              (res nil))
972         (declare (simple-string name)
973                  (fixnum len)
974                  (list res))
975
976         ;; Find matching commands, punting if exact match.
977         (flet ((match-command (ele)
978                  (let* ((str (car ele))
979                         (str-len (length str)))
980                    (declare (simple-string str)
981                             (fixnum str-len))
982                    (cond ((< str-len len))
983                          ((= str-len len)
984                           (when (string= name str :end1 len :end2 len)
985                             (return-from debug-command-p (cdr ele))))
986                          ((string= name str :end1 len :end2 len)
987                           (push ele res))))))
988           (mapc #'match-command *debug-commands*)
989           (mapc #'match-command other-commands))
990
991         ;; Return the right value.
992         (cond ((not res) nil)
993               ((= (length res) 1)
994                (cdar res))
995               (t ; Just return the names.
996                (do ((cmds res (cdr cmds)))
997                    ((not cmds) res)
998                  (setf (car cmds) (caar cmds))))))))
999
1000 ;;; Returns a list of debug commands (in the same format as *debug-commands*)
1001 ;;; that invoke each active restart.
1002 ;;;
1003 ;;; Two commands are made for each restart: one for the number, and one for
1004 ;;; the restart name (unless it's been shadowed by an earlier restart of the
1005 ;;; same name).
1006 (defun make-restart-commands (&optional (restarts *debug-restarts*))
1007   (let ((commands)
1008         (num 0))                        ; better be the same as show-restarts!
1009     (dolist (restart restarts)
1010       (let ((name (string (restart-name restart))))
1011         (unless (find name commands :key #'car :test #'string=)
1012           (let ((restart-fun
1013                  #'(lambda ()
1014                      (invoke-restart-interactively restart))))
1015             (push (cons name restart-fun) commands)
1016             (push (cons (format nil "~D" num) restart-fun) commands))))
1017       (incf num))
1018     commands))
1019 \f
1020 ;;;; frame-changing commands
1021
1022 (def-debug-command "UP" ()
1023   (let ((next (sb!di:frame-up *current-frame*)))
1024     (cond (next
1025            (setf *current-frame* next)
1026            (print-frame-call next))
1027           (t
1028            (format t "~&Top of stack.")))))
1029
1030 (def-debug-command "DOWN" ()
1031   (let ((next (sb!di:frame-down *current-frame*)))
1032     (cond (next
1033            (setf *current-frame* next)
1034            (print-frame-call next))
1035           (t
1036            (format t "~&Bottom of stack.")))))
1037
1038 (def-debug-command-alias "D" "DOWN")
1039
1040 (def-debug-command "TOP" ()
1041   (do ((prev *current-frame* lead)
1042        (lead (sb!di:frame-up *current-frame*) (sb!di:frame-up lead)))
1043       ((null lead)
1044        (setf *current-frame* prev)
1045        (print-frame-call prev))))
1046
1047 (def-debug-command "BOTTOM" ()
1048   (do ((prev *current-frame* lead)
1049        (lead (sb!di:frame-down *current-frame*) (sb!di:frame-down lead)))
1050       ((null lead)
1051        (setf *current-frame* prev)
1052        (print-frame-call prev))))
1053
1054 (def-debug-command-alias "B" "BOTTOM")
1055
1056 (def-debug-command "FRAME" (&optional
1057                             (n (read-prompting-maybe "frame number: ")))
1058   (setf *current-frame*
1059         (multiple-value-bind (next-frame-fun limit-string)
1060             (if (< n (sb!di:frame-number *current-frame*))
1061                 (values #'sb!di:frame-up "top")
1062               (values #'sb!di:frame-down "bottom"))
1063           (do ((frame *current-frame*))
1064               ((= n (sb!di:frame-number frame))
1065                frame)
1066             (let ((next-frame (funcall next-frame-fun frame)))
1067               (cond (next-frame
1068                      (setf frame next-frame))
1069                     (t
1070                      (format t
1071                              "The ~A of the stack was encountered.~%"
1072                              limit-string)
1073                      (return frame)))))))
1074   (print-frame-call *current-frame*))
1075
1076 (def-debug-command-alias "F" "FRAME")
1077 \f
1078 ;;;; commands for entering and leaving the debugger
1079
1080 (def-debug-command "QUIT" ()
1081   (throw 'sb!impl::top-level-catcher nil))
1082
1083 (def-debug-command "GO" ()
1084   (continue *debug-condition*)
1085   (error "There is no restart named CONTINUE."))
1086
1087 (def-debug-command "RESTART" ()
1088   (let ((num (read-if-available :prompt)))
1089     (when (eq num :prompt)
1090       (show-restarts *debug-restarts*)
1091       (write-string "restart: ")
1092       (force-output)
1093       (setf num (read *standard-input*)))
1094     (let ((restart (typecase num
1095                      (unsigned-byte
1096                       (nth num *debug-restarts*))
1097                      (symbol
1098                       (find num *debug-restarts* :key #'restart-name
1099                             :test #'(lambda (sym1 sym2)
1100                                       (string= (symbol-name sym1)
1101                                                (symbol-name sym2)))))
1102                      (t
1103                       (format t "~S is invalid as a restart name.~%" num)
1104                       (return-from restart-debug-command nil)))))
1105       (if restart
1106           (invoke-restart-interactively restart)
1107           ;; FIXME: Even if this isn't handled by WARN, it probably
1108           ;; shouldn't go to *STANDARD-OUTPUT*, but *ERROR-OUTPUT* or
1109           ;; *QUERY-IO* or something. Look through this file to
1110           ;; straighten out stream usage.
1111           (princ "There is no such restart.")))))
1112 \f
1113 ;;;; information commands
1114
1115 (def-debug-command "HELP" ()
1116   ;; CMU CL had a little toy pager here, but "if you aren't running
1117   ;; ILISP (or a smart windowing system, or something) you deserve to
1118   ;; lose", so we've dropped it in SBCL. However, in case some
1119   ;; desperate holdout is running this on a dumb terminal somewhere,
1120   ;; we tell him where to find the message stored as a string.
1121   (format *debug-io*
1122           "~&~a~2%(The HELP string is stored in ~S.)~%"
1123           *debug-help-string*
1124           '*debug-help-string*))
1125
1126 (def-debug-command-alias "?" "HELP")
1127
1128 (def-debug-command "ERROR" ()
1129   (format t "~A~%" *debug-condition*)
1130   (show-restarts *debug-restarts*))
1131
1132 (def-debug-command "BACKTRACE" ()
1133   (backtrace (read-if-available most-positive-fixnum)))
1134
1135 (def-debug-command "PRINT" ()
1136   (print-frame-call *current-frame*))
1137
1138 (def-debug-command-alias "P" "PRINT")
1139
1140 (def-debug-command "LIST-LOCALS" ()
1141   (let ((d-fun (sb!di:frame-debug-function *current-frame*)))
1142     (if (sb!di:debug-var-info-available d-fun)
1143         (let ((*standard-output* *debug-io*)
1144               (location (sb!di:frame-code-location *current-frame*))
1145               (prefix (read-if-available nil))
1146               (any-p nil)
1147               (any-valid-p nil))
1148           (dolist (v (sb!di:ambiguous-debug-vars
1149                         d-fun
1150                         (if prefix (string prefix) "")))
1151             (setf any-p t)
1152             (when (eq (sb!di:debug-var-validity v location) :valid)
1153               (setf any-valid-p t)
1154               (format t "~S~:[#~D~;~*~]  =  ~S~%"
1155                       (sb!di:debug-var-symbol v)
1156                       (zerop (sb!di:debug-var-id v))
1157                       (sb!di:debug-var-id v)
1158                       (sb!di:debug-var-value v *current-frame*))))
1159
1160           (cond
1161            ((not any-p)
1162             (format t "There are no local variables ~@[starting with ~A ~]~
1163                        in the function."
1164                     prefix))
1165            ((not any-valid-p)
1166             (format t "All variables ~@[starting with ~A ~]currently ~
1167                        have invalid values."
1168                     prefix))))
1169         (write-line "There is no variable information available."))))
1170
1171 (def-debug-command-alias "L" "LIST-LOCALS")
1172
1173 (def-debug-command "SOURCE" ()
1174   (fresh-line)
1175   (print-code-location-source-form (sb!di:frame-code-location *current-frame*)
1176                                    (read-if-available 0)))
1177 \f
1178 ;;;; source location printing
1179
1180 ;;; We cache a stream to the last valid file debug source so that we won't have
1181 ;;; to repeatedly open the file.
1182 ;;; KLUDGE: This sounds like a bug, not a feature. Opening files is fast
1183 ;;; in the 1990s, so the benefit is negligible, less important than the
1184 ;;; potential of extra confusion if someone changes the source during
1185 ;;; a debug session and the change doesn't show up. And removing this
1186 ;;; would simplify the system, which I like. -- WHN 19990903
1187 (defvar *cached-debug-source* nil)
1188 (declaim (type (or sb!di:debug-source null) *cached-debug-source*))
1189 (defvar *cached-source-stream* nil)
1190 (declaim (type (or stream null) *cached-source-stream*))
1191
1192 ;;; To suppress the read-time evaluation #. macro during source read,
1193 ;;; *READTABLE* is modified. *READTABLE* is cached to avoid
1194 ;;; copying it each time, and invalidated when the
1195 ;;; *CACHED-DEBUG-SOURCE* has changed.
1196 (defvar *cached-readtable* nil)
1197 (declaim (type (or readtable null) *cached-readtable*))
1198
1199 (pushnew #'(lambda ()
1200              (setq *cached-debug-source* nil *cached-source-stream* nil
1201                    *cached-readtable* nil))
1202          sb!int:*before-save-initializations*)
1203
1204 ;;; We also cache the last top-level form that we printed a source for so that
1205 ;;; we don't have to do repeated reads and calls to FORM-NUMBER-TRANSLATIONS.
1206 (defvar *cached-top-level-form-offset* nil)
1207 (declaim (type (or sb!kernel:index null) *cached-top-level-form-offset*))
1208 (defvar *cached-top-level-form*)
1209 (defvar *cached-form-number-translations*)
1210
1211 ;;; Given a code location, return the associated form-number translations and
1212 ;;; the actual top-level form. We check our cache --- if there is a miss, we
1213 ;;; dispatch on the kind of the debug source.
1214 (defun get-top-level-form (location)
1215   (let ((d-source (sb!di:code-location-debug-source location)))
1216     (if (and (eq d-source *cached-debug-source*)
1217              (eql (sb!di:code-location-top-level-form-offset location)
1218                   *cached-top-level-form-offset*))
1219         (values *cached-form-number-translations* *cached-top-level-form*)
1220         (let* ((offset (sb!di:code-location-top-level-form-offset location))
1221                (res
1222                 (ecase (sb!di:debug-source-from d-source)
1223                   (:file (get-file-top-level-form location))
1224                   (:lisp (svref (sb!di:debug-source-name d-source) offset)))))
1225           (setq *cached-top-level-form-offset* offset)
1226           (values (setq *cached-form-number-translations*
1227                         (sb!di:form-number-translations res offset))
1228                   (setq *cached-top-level-form* res))))))
1229
1230 ;;; Locates the source file (if it still exists) and grabs the top-level form.
1231 ;;; If the file is modified, we use the top-level-form offset instead of the
1232 ;;; recorded character offset.
1233 (defun get-file-top-level-form (location)
1234   (let* ((d-source (sb!di:code-location-debug-source location))
1235          (tlf-offset (sb!di:code-location-top-level-form-offset location))
1236          (local-tlf-offset (- tlf-offset
1237                               (sb!di:debug-source-root-number d-source)))
1238          (char-offset
1239           (aref (or (sb!di:debug-source-start-positions d-source)
1240                     (error "no start positions map"))
1241                 local-tlf-offset))
1242          (name (sb!di:debug-source-name d-source)))
1243     (unless (eq d-source *cached-debug-source*)
1244       (unless (and *cached-source-stream*
1245                    (equal (pathname *cached-source-stream*)
1246                           (pathname name)))
1247         (setq *cached-readtable* nil)
1248         (when *cached-source-stream* (close *cached-source-stream*))
1249         (setq *cached-source-stream* (open name :if-does-not-exist nil))
1250         (unless *cached-source-stream*
1251           (error "The source file no longer exists:~%  ~A" (namestring name)))
1252         (format t "~%; file: ~A~%" (namestring name)))
1253
1254         (setq *cached-debug-source*
1255               (if (= (sb!di:debug-source-created d-source)
1256                      (file-write-date name))
1257                   d-source nil)))
1258
1259     (cond
1260      ((eq *cached-debug-source* d-source)
1261       (file-position *cached-source-stream* char-offset))
1262      (t
1263       (format t "~%; File has been modified since compilation:~%;   ~A~@
1264                  ; Using form offset instead of character position.~%"
1265               (namestring name))
1266       (file-position *cached-source-stream* 0)
1267       (let ((*read-suppress* t))
1268         (dotimes (i local-tlf-offset)
1269           (read *cached-source-stream*)))))
1270     (unless *cached-readtable*
1271       (setq *cached-readtable* (copy-readtable))
1272       (set-dispatch-macro-character
1273        #\# #\.
1274        #'(lambda (stream sub-char &rest rest)
1275            (declare (ignore rest sub-char))
1276            (let ((token (read stream t nil t)))
1277              (format nil "#.~S" token)))
1278        *cached-readtable*))
1279     (let ((*readtable* *cached-readtable*))
1280       (read *cached-source-stream*))))
1281
1282 (defun print-code-location-source-form (location context)
1283   (let* ((location (maybe-block-start-location location))
1284          (form-num (sb!di:code-location-form-number location)))
1285     (multiple-value-bind (translations form) (get-top-level-form location)
1286       (unless (< form-num (length translations))
1287         (error "The source path no longer exists."))
1288       (prin1 (sb!di:source-path-context form
1289                                         (svref translations form-num)
1290                                         context)))))
1291 \f
1292 ;;; breakpoint and step commands
1293
1294 ;;; Step to the next code-location.
1295 (def-debug-command "STEP" ()
1296   (setf *number-of-steps* (read-if-available 1))
1297   (set-step-breakpoint *current-frame*)
1298   (continue *debug-condition*)
1299   (error "couldn't continue"))
1300
1301 ;;; List possible breakpoint locations, which ones are active, and where GO
1302 ;;; will continue. Set *POSSIBLE-BREAKPOINTS* to the code-locations which can
1303 ;;; then be used by sbreakpoint.
1304 (def-debug-command "LIST-LOCATIONS" ()
1305   (let ((df (read-if-available *default-breakpoint-debug-function*)))
1306     (cond ((consp df)
1307            (setf df (sb!di:function-debug-function (eval df)))
1308            (setf *default-breakpoint-debug-function* df))
1309           ((or (eq ':c df)
1310                (not *default-breakpoint-debug-function*))
1311            (setf df (sb!di:frame-debug-function *current-frame*))
1312            (setf *default-breakpoint-debug-function* df)))
1313     (setf *possible-breakpoints* (possible-breakpoints df)))
1314   (let ((continue-at (sb!di:frame-code-location *current-frame*)))
1315     (let ((active (location-in-list *default-breakpoint-debug-function*
1316                                     *breakpoints* :function-start))
1317           (here (sb!di:code-location=
1318                  (sb!di:debug-function-start-location
1319                   *default-breakpoint-debug-function*) continue-at)))
1320       (when (or active here)
1321         (format t "::FUNCTION-START ")
1322         (when active (format t " *Active*"))
1323         (when here (format t " *Continue here*"))))
1324
1325     (let ((prev-location nil)
1326           (prev-num 0)
1327           (this-num 0))
1328       (flet ((flush ()
1329                (when prev-location
1330                  (let ((this-num (1- this-num)))
1331                    (if (= prev-num this-num)
1332                        (format t "~&~D: " prev-num)
1333                        (format t "~&~D-~D: " prev-num this-num)))
1334                  (print-code-location-source-form prev-location 0)
1335                  (when *print-location-kind*
1336                    (format t "~S " (sb!di:code-location-kind prev-location)))
1337                  (when (location-in-list prev-location *breakpoints*)
1338                    (format t " *Active*"))
1339                  (when (sb!di:code-location= prev-location continue-at)
1340                    (format t " *Continue here*")))))
1341         
1342         (dolist (code-location *possible-breakpoints*)
1343           (when (or *print-location-kind*
1344                     (location-in-list code-location *breakpoints*)
1345                     (sb!di:code-location= code-location continue-at)
1346                     (not prev-location)
1347                     (not (eq (sb!di:code-location-debug-source code-location)
1348                              (sb!di:code-location-debug-source prev-location)))
1349                     (not (eq (sb!di:code-location-top-level-form-offset
1350                               code-location)
1351                              (sb!di:code-location-top-level-form-offset
1352                               prev-location)))
1353                     (not (eq (sb!di:code-location-form-number code-location)
1354                              (sb!di:code-location-form-number prev-location))))
1355             (flush)
1356             (setq prev-location code-location  prev-num this-num))
1357
1358           (incf this-num))))
1359
1360     (when (location-in-list *default-breakpoint-debug-function*
1361                             *breakpoints*
1362                             :function-end)
1363       (format t "~&::FUNCTION-END *Active* "))))
1364
1365 (def-debug-command-alias "LL" "LIST-LOCATIONS")
1366
1367 ;;; Set breakpoint at the given number.
1368 (def-debug-command "BREAKPOINT" ()
1369   (let ((index (read-prompting-maybe "location number, :START, or :END: "))
1370         (break t)
1371         (condition t)
1372         (print nil)
1373         (print-functions nil)
1374         (function nil)
1375         (bp)
1376         (place *default-breakpoint-debug-function*))
1377     (flet ((get-command-line ()
1378              (let ((command-line nil)
1379                    (unique '(nil)))
1380                (loop
1381                  (let ((next-input (read-if-available unique)))
1382                    (when (eq next-input unique) (return))
1383                    (push next-input command-line)))
1384                (nreverse command-line)))
1385            (set-vars-from-command-line (command-line)
1386              (do ((arg (pop command-line) (pop command-line)))
1387                  ((not arg))
1388                (ecase arg
1389                  (:condition (setf condition (pop command-line)))
1390                  (:print (push (pop command-line) print))
1391                  (:break (setf break (pop command-line)))
1392                  (:function
1393                   (setf function (eval (pop command-line)))
1394                   (setf *default-breakpoint-debug-function*
1395                         (sb!di:function-debug-function function))
1396                   (setf place *default-breakpoint-debug-function*)
1397                   (setf *possible-breakpoints*
1398                         (possible-breakpoints
1399                          *default-breakpoint-debug-function*))))))
1400            (setup-function-start ()
1401              (let ((code-loc (sb!di:debug-function-start-location place)))
1402                (setf bp (sb!di:make-breakpoint #'main-hook-function
1403                                                place
1404                                                :kind :function-start))
1405                (setf break (sb!di:preprocess-for-eval break code-loc))
1406                (setf condition (sb!di:preprocess-for-eval condition code-loc))
1407                (dolist (form print)
1408                  (push (cons (sb!di:preprocess-for-eval form code-loc) form)
1409                        print-functions))))
1410            (setup-function-end ()
1411              (setf bp
1412                    (sb!di:make-breakpoint #'main-hook-function
1413                                           place
1414                                           :kind :function-end))
1415              (setf break
1416                    ;; FIXME: These and any other old (COERCE `(LAMBDA ..) ..)
1417                    ;; forms should be converted to shiny new (LAMBDA ..) forms.
1418                    ;; (Search the sources for "coerce.*\(lambda".)
1419                    (coerce `(lambda (dummy)
1420                               (declare (ignore dummy)) ,break)
1421                            'function))
1422              (setf condition (coerce `(lambda (dummy)
1423                                         (declare (ignore dummy)) ,condition)
1424                                      'function))
1425              (dolist (form print)
1426                (push (cons
1427                       (coerce `(lambda (dummy)
1428                                  (declare (ignore dummy)) ,form) 'function)
1429                       form)
1430                      print-functions)))
1431            (setup-code-location ()
1432              (setf place (nth index *possible-breakpoints*))
1433              (setf bp (sb!di:make-breakpoint #'main-hook-function
1434                                              place
1435                                              :kind :code-location))
1436              (dolist (form print)
1437                (push (cons
1438                       (sb!di:preprocess-for-eval form place)
1439                       form)
1440                      print-functions))
1441              (setf break (sb!di:preprocess-for-eval break place))
1442              (setf condition (sb!di:preprocess-for-eval condition place))))
1443       (set-vars-from-command-line (get-command-line))
1444       (cond
1445        ((or (eq index :start) (eq index :s))
1446         (setup-function-start))
1447        ((or (eq index :end) (eq index :e))
1448         (setup-function-end))
1449        (t
1450         (setup-code-location)))
1451       (sb!di:activate-breakpoint bp)
1452       (let* ((new-bp-info (create-breakpoint-info place bp index
1453                                                   :break break
1454                                                   :print print-functions
1455                                                   :condition condition))
1456              (old-bp-info (location-in-list new-bp-info *breakpoints*)))
1457         (when old-bp-info
1458           (sb!di:deactivate-breakpoint (breakpoint-info-breakpoint
1459                                         old-bp-info))
1460           (setf *breakpoints* (remove old-bp-info *breakpoints*))
1461           (format t "previous breakpoint removed~%"))
1462         (push new-bp-info *breakpoints*))
1463       (print-breakpoint-info (first *breakpoints*))
1464       (format t "~&added"))))
1465
1466 (def-debug-command-alias "BP" "BREAKPOINT")
1467
1468 ;;; List all breakpoints which are set.
1469 (def-debug-command "LIST-BREAKPOINTS" ()
1470   (setf *breakpoints*
1471         (sort *breakpoints* #'< :key #'breakpoint-info-breakpoint-number))
1472   (dolist (info *breakpoints*)
1473     (print-breakpoint-info info)))
1474
1475 (def-debug-command-alias "LB" "LIST-BREAKPOINTS")
1476 (def-debug-command-alias "LBP" "LIST-BREAKPOINTS")
1477
1478 ;;; Remove breakpoint N, or remove all breakpoints if no N given.
1479 (def-debug-command "DELETE-BREAKPOINT" ()
1480   (let* ((index (read-if-available nil))
1481          (bp-info
1482           (find index *breakpoints* :key #'breakpoint-info-breakpoint-number)))
1483     (cond (bp-info
1484            (sb!di:delete-breakpoint (breakpoint-info-breakpoint bp-info))
1485            (setf *breakpoints* (remove bp-info *breakpoints*))
1486            (format t "breakpoint ~S removed~%" index))
1487           (index (format t "The breakpoint doesn't exist."))
1488           (t
1489            (dolist (ele *breakpoints*)
1490              (sb!di:delete-breakpoint (breakpoint-info-breakpoint ele)))
1491            (setf *breakpoints* nil)
1492            (format t "all breakpoints deleted~%")))))
1493
1494 (def-debug-command-alias "DBP" "DELETE-BREAKPOINT")
1495 \f
1496 ;;; miscellaneous commands
1497
1498 (def-debug-command "DESCRIBE" ()
1499   (let* ((curloc (sb!di:frame-code-location *current-frame*))
1500          (debug-fun (sb!di:code-location-debug-function curloc))
1501          (function (sb!di:debug-function-function debug-fun)))
1502     (if function
1503         (describe function)
1504         (format t "can't figure out the function for this frame"))))
1505 \f
1506 ;;;; debug loop command utilities
1507
1508 (defun read-prompting-maybe (prompt &optional (in *standard-input*)
1509                                     (out *standard-output*))
1510   (unless (sb!int:listen-skip-whitespace in)
1511     (princ prompt out)
1512     (force-output out))
1513   (read in))
1514
1515 (defun read-if-available (default &optional (stream *standard-input*))
1516   (if (sb!int:listen-skip-whitespace stream)
1517       (read stream)
1518       default))