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