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