Skip to content
Snippets Groups Projects
debug.lisp 55.1 KiB
Newer Older
ram's avatar
ram committed
;;; -*- Mode: Lisp; Package: Debug; Log: code.log -*-
;;;
;;; **********************************************************************
;;; This code was written as part of the CMU Common Lisp project at
;;; Carnegie Mellon University, and has been placed in the public domain.
;;;
(ext:file-comment
  "$Header: /Volumes/share2/src/cmucl/cvs2git/cvsroot/src/code/debug.lisp,v 1.46 1997/12/07 18:22:25 dtc Exp $")
ram's avatar
ram committed
;;; **********************************************************************
;;;
chiles's avatar
 
chiles committed
;;; CMU Common Lisp Debugger.  This includes a basic command-line oriented
;;; debugger interface as well as support for Hemlock to deliver debugger
;;; commands to a slave Lisp.
ram's avatar
ram committed
;;;
;;; Written by Bill Chiles.
ram's avatar
ram committed
;;;

ram's avatar
ram committed

(export '(internal-debug *in-the-debugger* backtrace *flush-debug-errors*
ram's avatar
ram committed
	  *debug-print-level* *debug-print-length* *debug-prompt*
	  *help-line-scroll-count* *stack-top-hint*
chiles's avatar
 
chiles committed

	  *auto-eval-in-frame* var arg
	  *only-block-start-locations* *print-location-kind*
ram's avatar
ram committed

chiles's avatar
 
chiles committed
	  do-debug-command))
ram's avatar
ram committed

(in-package "LISP")
(export '(invoke-debugger *debugger-hook*))

(in-package "DEBUG")

;;;
;;; Used to communicate to debug-loop that we are at a step breakpoint.
;;;
(define-condition step-condition (simple-condition) ())
ram's avatar
ram committed
;;;; Variables, parameters, and constants.

(defparameter *debug-print-level* 3
  "*PRINT-LEVEL* is bound to this value when debug prints a function call.  If
ram's avatar
ram committed
  null, use *PRINT-LEVEL*")

(defparameter *debug-print-length* 5
  "*PRINT-LENGTH* is bound to this value when debug prints a function call.  If
  null, use *PRINT-LENGTH*.")

(defvar *in-the-debugger* nil
  "This is T while in the debugger.")

(defvar *debug-command-level* 0
  "Pushes and pops/exits inside the debugger change this.")

(defvar *stack-top-hint* nil
  "If this is bound before the debugger is invoked, it is used as the stack
(defvar *real-stack-top* nil)

(defvar *current-frame* nil)

;;; DEBUG-PROMPT -- Internal.
;;;
;;; This is the default for *debug-prompt*.
;;;
(defun debug-prompt ()
  (let ((*standard-output* *debug-io*))
    (terpri)
    (prin1 (di:frame-number *current-frame*))
    (dotimes (i *debug-command-level*) (princ "]"))
    (princ " ")
    (force-output)))

(defparameter *debug-prompt* #'debug-prompt
  "This is a function of no arguments that prints the debugger prompt
   on *debug-io*.")

(defconstant debug-help-string
"
The prompt is right square brackets, the number indicating how many
  recursive command loops you are in.
Debug commands do not affect * and friends, but evaluation in the debug loop
  do affect these variables.
Any command may be uniquely abbreviated.

Getting in and out of DEBUG:
  Q        throws to top level.
  GO       calls CONTINUE which tries to proceed with the restart 'continue.
  RESTART  invokes restart numbered as shown (prompt if not given).
  ERROR    prints the error condition and restart cases.
  FLUSH    toggles *flush-debug-errors*, which is initially t.
 
  The name of any restart, or its number, is a valid command, and is the same
    as using RESTART to invoke that restart.

Changing frames:
  U  up frame        D  down frame       T  top frame       B  bottom frame

  F n   goes to frame n.

Inspecting frames:
  BACKTRACE [n]  shows n frames going down the stack.
  L              lists locals in current function.
  P, PP          displays current function call.
  SOURCE [n]     displays frame's source form with n levels of enclosing forms.
  VSOURCE [n]    displays frame's source form without any ellipsis.

Breakpoints and steps:
  LIST-LOCATIONS [{function | :c}]  list the locations for breakpoints.
    Specify :c for the current frame.  Abbreviation: LL
  LIST-BREAKPOINTS                  list the active breakpoints.
    Abbreviations: LB, LBP
  DELETE-BREAKPOINT [n]             remove breakpoint n or all breakpoints.
    Abbreviations: DEL, DBP    
  BREAKPOINT {n | :end | :start} [:break form] [:function function]
    [{:print form}*] [:condition form]    set a breakpoint.
    Abbreviations: BR, BP
  STEP [n]                          step to the next location or step n times.

Function and macro commands:
 (DEBUG:DEBUG-RETURN expression)
    returns expression's values from the current frame, exiting the debugger.
 (DEBUG:ARG n)
    returns the n'th argument, remaining in the debugger.
 (DEBUG:VAR string-or-symbol [id])
    returns the specified variable's value, remaining in the debugger.

See the CMU Common Lisp User's Manual for more information.
")


;;;; Breakpoint state:

(defvar *only-block-start-locations* nil
ram's avatar
ram committed
  "When true, the LIST-LOCATIONS command only displays block start locations.
   Otherwise, all locations are displayed.")

(defvar *print-location-kind* nil
ram's avatar
ram committed
  "If true, list the code location type in the LIST-LOCATIONS command.")

;;; A list of the types of code-locations that should not be stepped to and
ram's avatar
ram committed
;;; should not be listed when listing breakpoints.
;;;
(defvar *bad-code-location-types* '(:call-site :internal-error))
(declaim (type list *bad-code-location-types*))
ram's avatar
ram committed

;;; Code locations of the possible breakpoints
;;;
(defvar *possible-breakpoints*)
(declaim (type list *possible-breakpoints*))

;;; A list of the made and active breakpoints, each is a breakpoint-info
ram's avatar
ram committed
;;;
(defvar *breakpoints* nil)
(declaim (type list *breakpoints*))

;;; A list of breakpoint-info structures of the made and active step
;;; breakpoints.
;;;
(defvar *step-breakpoints* nil)  
(declaim (type list *step-breakpoints*))

;;; Number of times left to step.
ram's avatar
ram committed
;;;
(defvar *number-of-steps* 1)
(declaim (type integer *number-of-steps*))

;;; Used when listing and setting breakpoints.
ram's avatar
ram committed
;;;
(defvar *default-breakpoint-debug-function* nil)
(declaim (type (or list di:debug-function) *default-breakpoint-debug-function*))
ram's avatar
ram committed


;;;; Code location utilities:

;;; FIRST-CODE-LOCATION -- Internal.
;;;
;;; Returns the first code-location in the passed debug block
;;;
(defun first-code-location (debug-block)
  (let ((found nil)
	(first-code-location nil))
    (di:do-debug-block-locations (code-location debug-block)
      (unless found 
	(setf first-code-location code-location)
	(setf found t)))
    first-code-location))

;;; NEXT-CODE-LOCATIONS -- Internal.
;;;
ram's avatar
ram committed
;;; Returns a list of the next code-locations following the one passed.  One of
;;; the *bad-code-location-types* will not be returned.
;;;
(defun next-code-locations (code-location)
  (let ((debug-block (di:code-location-debug-block code-location))
	(block-code-locations nil))
ram's avatar
ram committed
    (di:do-debug-block-locations (block-code-location debug-block)
      (unless (member (di:code-location-kind block-code-location)
		      *bad-code-location-types*)
	(push block-code-location block-code-locations)))
    (setf block-code-locations (nreverse block-code-locations))
    (let* ((code-loc-list (rest (member code-location block-code-locations
					:test #'di:code-location=)))
	   (next-list (cond (code-loc-list
			     (list (first code-loc-list)))
			    ((map 'list #'first-code-location
				  (di:debug-block-successors debug-block)))
			    (t nil))))
      (when (and (= (length next-list) 1)
		 (di:code-location= (first next-list) code-location))
	(setf next-list (next-code-locations (first next-list))))
      next-list)))

;;; POSSIBLE-BREAKPOINTS -- Internal.
;;;  
;;; Returns a list of code-locations of the possible breakpoints of the 
;;; debug-function passed.
;;;
(defun possible-breakpoints (debug-function)
  (let ((possible-breakpoints nil))
    (di:do-debug-function-blocks (debug-block debug-function)
      (unless (di:debug-block-elsewhere-p debug-block)
	(if *only-block-start-locations*
	    (push (first-code-location debug-block) possible-breakpoints)
	    (di:do-debug-block-locations (code-location debug-block)
	      (when (not (member (di:code-location-kind code-location)
				 *bad-code-location-types*))
		(push code-location possible-breakpoints))))))
    (nreverse possible-breakpoints)))

;;; LOCATION-IN-LIST -- Internal.
;;;
;;; Searches the info-list for the item passed (code-location, debug-function,
;;; or breakpoint-info).  If the item passed is a debug function then kind will
;;; be compared if it was specified.  The kind if also compared if a
;;; breakpoint-info is passed since it's in the breakpoint.  The info structure
;;; is returned if found.
;;;
(defun location-in-list (place info-list &optional (kind nil)) 
  (when (breakpoint-info-p place)
ram's avatar
ram committed
    (setf kind (di:breakpoint-kind (breakpoint-info-breakpoint place)))
    (setf place (breakpoint-info-place place)))
  (cond ((di:code-location-p place)
	 (find place info-list
	       :key #'breakpoint-info-place
	       :test #'(lambda (x y) (and (di:code-location-p y)
					  (di:code-location= x y)))))
	(t
	 (find place info-list
	       :test #'(lambda (x-debug-function y-info)
			 (let ((y-place (breakpoint-info-place y-info))
			       (y-breakpoint (breakpoint-info-breakpoint
					      y-info)))
			   (and (di:debug-function-p y-place)
				(eq x-debug-function y-place)
				(or (not kind)
				    (eq kind (di:breakpoint-kind
					      y-breakpoint))))))))))


;;; MAYBE-BLOCK-START-LOCATION  --  Internal.
;;;
;;; If Loc is an unknown location, then try to find the block start location.
;;; Used by source printing to some information instead of none for the user.
;;;
(defun maybe-block-start-location (loc)
  (if (di:code-location-unknown-p loc)
      (let* ((block (di:code-location-debug-block loc))
	     (start (di:do-debug-block-locations (loc block)
		      (return loc))))
	(cond ((and (not (di:debug-block-elsewhere-p block))
		    start)
	       (format t "~%Unknown location: using block start.~%")
	       start)
	      (t
	       loc)))
      loc))


;;;; The BREAKPOINT-INFO structure:

;;; Hold info about made breakpoints
;;;
(defstruct breakpoint-info
  ;;
  ;; Where we are going to stop.
  (place (required-argument) :type (or di:code-location di:debug-function)) 
  ;;
  ;; The breakpoint returned by di:make-breakpoint.
  (breakpoint (required-argument) :type di:breakpoint)
  ;;
  ;; Function returned from di:preprocess-for-eval.  If result is non-nil,
  ;; drop into the debugger.
  (break #'identity :type function)
  ;; 
  ;; Function returned from di:preprocess-for-eval.  If result is non-nil,
  ;; eval (each) print and print results.
  (condition #'identity :type function)
  ;;
  ;; List of functions from di:preprocess-for-eval to evaluate, results are
  ;; conditionally printed.  Car of each element is the function, cdr is the
  ;; form it goes with.
  (print nil :type list)
  ;;
  ;; The number used when listing the possible breakpoints within a function.
  ;; Could also be a symbol such as start or end.
  (code-location-number (required-argument) :type (or symbol integer))
  ;;
  ;; The number used when listing the breakpoints active and to delete
  ;; breakpoints. 
  (breakpoint-number (required-argument) :type integer))


;;; CREATE-BREAKPOINT-INFO -- Internal.
;;;
;;; Returns a new breakpoint-info structure with the info passed.
;;;
(defun create-breakpoint-info (place breakpoint code-location-number
				     &key (break #'identity)
				     (condition #'identity) (print nil))
  (setf *breakpoints*
	(sort *breakpoints* #'< :key #'breakpoint-info-breakpoint-number))
  (let ((breakpoint-number
	 (do ((i 1 (incf i)) (breakpoints *breakpoints* (rest breakpoints)))
	     ((or (> i (length *breakpoints*))
		  (not (= i (breakpoint-info-breakpoint-number
			     (first breakpoints)))))

	      i))))
    (make-breakpoint-info :place place :breakpoint breakpoint
			  :code-location-number code-location-number
			  :breakpoint-number breakpoint-number
			  :break break :condition condition :print print)))

;;; PRINT-BREAKPOINT-INFO -- Internal.
;;;
;;; Prints the breakpoint info for the breakpoint-info structure passed.
;;;
(defun print-breakpoint-info (breakpoint-info)
  (let ((place (breakpoint-info-place breakpoint-info))
	(bp-number (breakpoint-info-breakpoint-number breakpoint-info))
	(loc-number (breakpoint-info-code-location-number breakpoint-info)))
    (case (di:breakpoint-kind (breakpoint-info-breakpoint breakpoint-info))
      (:code-location 
       (print-code-location-source-form place 0)
       (format t "~&~S: ~S in ~S"
	       bp-number loc-number (di:debug-function-name
				      (di:code-location-debug-function place))))
      (:function-start
       (format t "~&~S: FUNCTION-START in ~S" bp-number
	       (di:debug-function-name place)))
      (:function-end
       (format t "~&~S: FUNCTION-END in ~S" bp-number
	       (di:debug-function-name place))))))



;;;; Main-hook-function for steps and breakpoints

;;; MAIN-HOOK-FUNCTION -- Internal.
;;;
;;; Must be passed as the hook function.  Keeps track of where step 
;;; breakpoints are.
;;;
(defun main-hook-function (current-frame breakpoint &optional return-vals
					 function-end-cookie)
  (setf *default-breakpoint-debug-function*
	(di:frame-debug-function current-frame))
  (dolist (step-info *step-breakpoints*)
    (di:delete-breakpoint (breakpoint-info-breakpoint step-info))
    (let ((bp-info (location-in-list step-info *breakpoints*)))
      (when bp-info
	(di:activate-breakpoint (breakpoint-info-breakpoint bp-info)))))
  (let ((*stack-top-hint* current-frame)
	(step-hit-info
	 (location-in-list (di:breakpoint-what breakpoint)
			   *step-breakpoints* (di:breakpoint-kind breakpoint)))
	(bp-hit-info
	 (location-in-list (di:breakpoint-what breakpoint)
			   *breakpoints* (di:breakpoint-kind breakpoint)))
	(break)
	(condition)
	(string ""))
    (setf *step-breakpoints* nil)
    (labels ((build-string (str)
	       (setf string (concatenate 'string string str)))
	     (print-common-info ()
	       (build-string 
		(with-output-to-string (*standard-output*)
		  (when function-end-cookie 
		    (format t "~%Return values: ~S" return-vals))
		  (when condition
		    (when (breakpoint-info-print bp-hit-info)
		      (format t "~%")
		      (print-frame-call current-frame))
		    (dolist (print (breakpoint-info-print bp-hit-info))
		      (format t "~& ~S = ~S" (rest print)
			      (funcall (first print) current-frame))))))))
      (when bp-hit-info
	(setf break (funcall (breakpoint-info-break bp-hit-info)
			     current-frame))
	(setf condition (funcall (breakpoint-info-condition bp-hit-info)
				 current-frame)))
      (cond ((and bp-hit-info step-hit-info (= 1 *number-of-steps*))
	     (build-string (format nil "~&*Step (to a breakpoint)*"))
	     (print-common-info)
	     (break string))
	    ((and bp-hit-info step-hit-info break)
	     (build-string (format nil "~&*Step (to a breakpoint)*"))
	     (print-common-info)
	     (break string))
	    ((and bp-hit-info step-hit-info)
	     (print-common-info)
	     (format t "~A" string)
	     (decf *number-of-steps*)
	     (set-step-breakpoint current-frame))
	    ((and step-hit-info (= 1 *number-of-steps*))
	     (build-string "*Step*")
ram's avatar
ram committed
	     (break (make-condition 'step-condition :format-control string)))
	    (step-hit-info
	     (decf *number-of-steps*)
	     (set-step-breakpoint current-frame))
	    (bp-hit-info
	     (when break
	       (build-string (format nil "~&*Breakpoint hit*")))
	     (print-common-info)
	     (if break
		 (break string)
		 (format t "~A" string)))
	    (t
	     (break "Error in main-hook-function: unknown breakpoint"))))))



;;; STEP -- Internal.
;;;
;;; Sets breakpoints at the next possible code-locations.  After calling
;;; this either (continue) if in the debugger or just let program flow
;;; return if in a hook function.
(defun set-step-breakpoint (frame)
  (cond
   ((di:debug-block-elsewhere-p (di:code-location-debug-block
				 (di:frame-code-location frame)))
ram's avatar
ram committed
    (format t "Cannot step, in elsewhere code~%"))
   (t
    (let* ((code-location (di:frame-code-location frame))
	   (next-code-locations (next-code-locations code-location)))
      (cond
       (next-code-locations
	(dolist (code-location next-code-locations)
	  (let ((bp-info (location-in-list code-location *breakpoints*)))
	      (di:deactivate-breakpoint (breakpoint-info-breakpoint bp-info))))
	  (let ((bp (di:make-breakpoint #'main-hook-function code-location
					:kind :code-location)))
	    (di:activate-breakpoint bp)
	    (push (create-breakpoint-info code-location bp 0)
		  *step-breakpoints*))))
       (t
	(let* ((debug-function (di:frame-debug-function *current-frame*))
	       (bp (di:make-breakpoint #'main-hook-function debug-function
ram's avatar
ram committed
	  (di:activate-breakpoint bp)
ram's avatar
ram committed
	  (push (create-breakpoint-info debug-function bp 0)
		*step-breakpoints*))))))))



;;;; Backtrace:

;;; BACKTRACE -- Public.
;;;
(defun backtrace (&optional (count most-positive-fixnum)
			    (*standard-output* *debug-io*))
  "Show a listing of the call stack going down from the current frame.  In the
   debugger, the current frame is indicated by the prompt.  Count is how many
   frames to show."
  (let ((*print-length* (or *debug-print-length* *print-length*))
	(*print-level* (or *debug-print-level* *print-level*)))
    (fresh-line *standard-output*)
    (do ((frame (if *in-the-debugger* *current-frame* (di:top-frame))
		(di:frame-down frame))
	 (count count (1- count)))
	((or (null frame) (zerop count)))
      (print-frame-call frame :number t))
    (fresh-line *standard-output*)
    (values)))


;;;; Frame printing:

(eval-when (compile eval)
ram's avatar
ram committed

;;; LAMBDA-LIST-ELEMENT-DISPATCH -- Internal.
;;;
;;; This is a convenient way to express what to do for each type of lambda-list
;;; element.
;;;
(defmacro lambda-list-element-dispatch (element &key required optional rest
						keyword deleted)
  `(etypecase ,element
     (di:debug-variable
      ,@required)
     (cons
      (ecase (car ,element)
	(:optional ,@optional)
	(:rest ,@rest)
	(:keyword ,@keyword)))
     (symbol
      (assert (eq ,element :deleted))
      ,@deleted)))

(defmacro lambda-var-dispatch (variable location deleted valid other)
  (let ((var (gensym)))
    `(let ((,var ,variable))
       (cond ((eq ,var :deleted) ,deleted)
	     ((eq (di:debug-variable-validity ,var ,location) :valid) ,valid)
ram's avatar
ram committed
	     (t ,other)))))
chiles's avatar
 
chiles committed

) ;EVAL-WHEN


;;; This is used in constructing arg lists for debugger printing when the arg
;;; list is unavailable, some arg is unavailable or unused, etc.
;;;
(defstruct (unprintable-object
	    (:constructor make-unprintable-object (string))
	    (:print-function (lambda (x s d)
			       (declare (ignore d))
			       (format s "#<~A>"
				       (unprintable-object-string x)))))
;;; PRINT-FRAME-CALL-1 -- Internal.
;;;
;;; This prints frame with verbosity level 1.  If we hit a rest-arg, 
chiles's avatar
 
chiles committed
;;; then print as many of the values as possible,
;;; punting the loop over lambda-list variables since any other arguments
;;; will be in the rest-arg's list of values.
;;;
(defun print-frame-call-1 (frame)
  (let* ((d-fun (di:frame-debug-function frame))
	 (loc (di:frame-code-location frame))
	 (results (list (di:debug-function-name d-fun))))
    (handler-case
	(dolist (ele (di:debug-function-lambda-list d-fun))
	  (lambda-list-element-dispatch ele
	    :required ((push (frame-call-arg ele loc frame) results))
	    :optional ((push (frame-call-arg (second ele) loc frame) results))
	    :keyword ((push (second ele) results)
		      (push (frame-call-arg (third ele) loc frame) results))
	    :deleted ((push (frame-call-arg ele loc frame) results))
	    :rest ((lambda-var-dispatch (second ele) loc
		     nil
		     (progn
		       (setf results
			     (append (reverse (di:debug-variable-value
					       (second ele) frame))
				     results))
		       (return))
		     (push (make-unprintable-object "unavaliable-rest-arg")
chiles's avatar
 
chiles committed
			   results)))))
      (di:lambda-list-unavailable
       ()
       (push (make-unprintable-object "lambda-list-unavailable") results)))
    (prin1 (mapcar #'ensure-printable-object (nreverse results)))
    (when (di:debug-function-kind d-fun)
chiles's avatar
 
chiles committed
      (write-char #\[)
      (prin1 (di:debug-function-kind d-fun))
      (write-char #\]))))

(defun ensure-printable-object (object)
  (handler-case
      (with-open-stream (out (make-broadcast-stream))
	(prin1 object out)
	object)
    (error (cond)
      (declare (ignore cond))
      (make-unprintable-object "error printing object"))))

(defun frame-call-arg (var location frame)
  (lambda-var-dispatch var location
    (make-unprintable-object "unused-arg")
    (di:debug-variable-value var frame)
ram's avatar
ram committed
    (make-unprintable-object "unavailable-arg")))
ram's avatar
ram committed
;;; PRINT-FRAME-CALL -- Interface
;;;
;;; This prints a representation of the function call causing frame to exist.
;;; Verbosity indicates the level of information to output; zero indicates just
;;; printing the debug-function's name, and one indicates displaying call-like,
;;; one-liner format with argument values.
;;;
(defun print-frame-call (frame &key
			       ((:print-length *print-length*)
				(or *debug-print-length* *print-length*))
			       ((:print-level *print-level*)
				(or *debug-print-level* *print-level*))
ram's avatar
ram committed
			       (number nil))
  (cond
   ((zerop verbosity)
    (when number
      (format t "~&~S: " (di:frame-number frame)))
    (format t "~S" frame))
   (t
    (when number
      (format t "~&~S: " (di:frame-number frame)))
    (print-frame-call-1 frame)))
  (when (>= verbosity 2)
    (let ((loc (di:frame-code-location frame)))
      (handler-case
	  (progn
	    (di:code-location-debug-block loc)
	    (format t "~%Source: ")
	    (print-code-location-source-form loc 0))
	(di:debug-condition (ignore) ignore)
	(error (cond) (format t "Error finding source: ~A" cond))))))
ram's avatar
ram committed

;;;; Invoke-debugger.

(defvar *debugger-hook* nil
  "This is either nil or a function of two arguments, a condition and the value
   of *debugger-hook*.  This function can either handle the condition or return
ram's avatar
ram committed
   which causes the standard debugger to execute.  The system passes the value
   of this variable to the function because it binds *debugger-hook* to nil
   around the invocation.")

;;; These are bound on each invocation of INVOKE-DEBUGGER.
;;;
(defvar *debug-restarts*)
(defvar *debug-condition*)

;;; INVOKE-DEBUGGER -- Public.
;;;
(defun invoke-debugger (condition)
  "The CMU Common Lisp debugger.  Type h for help."
  (when *debugger-hook*
    (let ((hook *debugger-hook*)
	  (*debugger-hook* nil))
      (funcall hook condition hook)))
  (unix:unix-sigsetmask 0)
  (let* ((*debug-condition* condition)
	 (*debug-restarts* (compute-restarts condition))
	 (*standard-input* *debug-io*)		;in case of setq
	 (*standard-output* *debug-io*)		;''  ''  ''  ''
	 (*error-output* *debug-io*)
ram's avatar
ram committed
	 ;; Rebind some printer control variables.
	 (kernel:*current-level* 0)
ram's avatar
ram committed
	 (*print-readably* nil)
	 (*read-eval* t))
    (format *error-output* "~2&~A~2&" *debug-condition*)
    (unless (typep condition 'step-condition)
      (show-restarts *debug-restarts* *error-output*))
    (internal-debug)))

ram's avatar
ram committed
;;; SHOW-RESTARTS -- Internal.
;;;
(defun show-restarts (restarts &optional (s *error-output*))
ram's avatar
ram committed
  (when restarts
    (format s "~&Restarts:~%")
    (let ((count 0)
	  (names-used '(nil))
	  (max-name-len 0))
      (dolist (restart restarts)
	(let ((name (restart-name restart)))
ram's avatar
ram committed
	  (when name
	    (let ((len (length (princ-to-string name))))
	      (when (> len max-name-len)
		(setf max-name-len len))))))
      (unless (zerop max-name-len)
ram's avatar
ram committed
	(incf max-name-len 3))
	(let ((name (restart-name restart)))
	  (cond ((member name names-used)
		 (format s "~& ~2D: ~@VT~A~%" count max-name-len restart))
		(t
		 (format s "~& ~2D: [~VA] ~A~%"
ram's avatar
ram committed
			 count (- max-name-len 3) name restart)
		 (push name names-used))))
	(incf count)))))

;;; INTERNAL-DEBUG -- Internal Interface.
;;;
;;; This calls DEBUG-LOOP, performing some simple initializations before doing
;;; so.  INVOKE-DEBUGGER calls this to actually get into the debugger.
;;; CONDITIONS::ERROR-ERROR calls this in emergencies to get into a debug
;;; prompt as quickly as possible with as little risk as possible for stepping
;;; on whatever is causing recursive errors.
(defun internal-debug ()
  (let ((*in-the-debugger* t)
	(*read-suppress* nil))
    (unless (typep *debug-condition* 'step-condition)
ram's avatar
ram committed
      (clear-input *debug-io*)
      (format *debug-io* "~2&Debug  (type H for help)~2%"))
chiles's avatar
 
chiles committed
    (debug-loop)))


chiles's avatar
 
chiles committed

(defvar *flush-debug-errors* t
  "When set, avoid calling INVOKE-DEBUGGER recursively when errors occur while
   executing in the debugger.  The 'flush' command toggles this.")

(defun debug-loop ()
  (let* ((*debug-command-level* (1+ *debug-command-level*))
chiles's avatar
 
chiles committed
	 (*real-stack-top* (di:top-frame))
	 (*stack-top* (or *stack-top-hint* *real-stack-top*))
chiles's avatar
 
chiles committed
	 (*current-frame* *stack-top*))
    (handler-bind ((di:debug-condition #'(lambda (condition)
					   (princ condition *debug-io*)
					   (throw 'debug-loop-catcher nil))))
      (fresh-line)
      (print-frame-call *current-frame* :verbosity 2)
      (loop
	(catch 'debug-loop-catcher
	  (handler-bind ((error #'(lambda (condition)
ram's avatar
ram committed
				    (when *flush-debug-errors*
				      (clear-input *debug-io*)
				      (princ condition)
				      (format t "~&Error flushed ...")
				      (throw 'debug-loop-catcher nil)))))
	    ;; Must bind level for restart function created by
ram's avatar
ram committed
	    ;; WITH-SIMPLE-RESTART.
	    (let ((level *debug-command-level*)
		  (restart-commands (make-restart-commands)))
	      (with-simple-restart (abort "Return to debug level ~D." level)
		(funcall *debug-prompt*)
		(let ((input (ext:get-stream-command *debug-io*)))
ram's avatar
ram committed
		  (cond (input
			 (let ((cmd-fun (debug-command-p
					 (ext:stream-command-name input)
					 restart-commands)))
			   (cond
			    ((not cmd-fun)
			     (error "Unknown stream-command -- ~S." input))
			    ((consp cmd-fun)
			     (error "Ambiguous debugger command: ~S." cmd-fun))
			    (t
			     (apply cmd-fun (ext:stream-command-args input))))))
			(t
			 (let* ((exp (read))
				(cmd-fun (debug-command-p exp restart-commands)))
			   (cond ((not cmd-fun)
				  (debug-eval-print exp))
				 ((consp cmd-fun)
				  (format t "~&Your command, ~S, is ambiguous:~%"
					  exp)
				  (dolist (ele cmd-fun)
				    (format t "   ~A~%" ele)))
				 (t
chiles's avatar
 
chiles committed
				  (funcall cmd-fun)))))))))))))))

(defvar *auto-eval-in-frame* t
  "When set (the default), evaluations in the debugger's command loop occur
   relative to the current frame's environment without the need of debugger
   forms that explicitly control this kind of evaluation.")

(defun debug-eval-print (exp)
  (setq +++ ++ ++ + + - - exp)
  (let* ((values (multiple-value-list
		  (if (and (fboundp 'compile) *auto-eval-in-frame*)
chiles's avatar
 
chiles committed
		      (di:eval-in-frame *current-frame* -)
		      (eval -))))
	 (*standard-output* *debug-io*))
    (fresh-line)
    (if values (prin1 (car values)))
    (dolist (x (cdr values))
      (fresh-line)
      (prin1 x))
    (setq /// // // / / values)
    (setq *** ** ** * * (car values))
    ;; Make sure nobody passes back an unbound marker.
    (unless (boundp '*)
      (setq * nil)
      (fresh-line)
      (princ "Setting * to NIL -- was unbound marker."))))

ram's avatar
ram committed

chiles's avatar
 
chiles committed

;;;; Debug loop functions.

;;; These commands are function, not really commands, so users can get their
;;; hands on the values returned.
;;;

(eval-when (eval compile)

(defmacro define-var-operation (ref-or-set &optional value-var)
  `(let* ((temp (etypecase name
		  (symbol (di:debug-function-symbol-variables
			   (di:frame-debug-function *current-frame*)
			   name))
		  (simple-string (di:ambiguous-debug-variables
				  (di:frame-debug-function *current-frame*)
				  name))))
	  (location (di:frame-code-location *current-frame*))
	  ;; Let's only deal with valid variables.
	  (vars (remove-if-not #'(lambda (v)
				   (eq (di:debug-variable-validity v location)
				       :valid))
			       temp)))
     (declare (list vars))
     (cond ((null vars)
	    (error "No known valid variables match ~S." name))
	   ((= (length vars) 1)
	    ,(ecase ref-or-set
	       (:ref
		'(di:debug-variable-value (car vars) *current-frame*))
	       (:set
		`(setf (di:debug-variable-value (car vars) *current-frame*)
		       ,value-var))))
	   (t
	    ;; Since we have more than one, first see if we have any
	    ;; variables that exactly match the specification.
	    (let* ((name (etypecase name
			   (symbol (symbol-name name))
			   (simple-string name)))
		   (exact (remove-if-not #'(lambda (v)
					     (string= (di:debug-variable-name v)
						      name))
					 vars))
		   (vars (or exact vars)))
	      (declare (simple-string name)
		       (list exact vars))
	      (cond
	       ;; Check now for only having one variable.
	       ((= (length vars) 1)
		,(ecase ref-or-set
		   (:ref
		    '(di:debug-variable-value (car vars) *current-frame*))
ram's avatar
ram committed
		   (:set
		    `(setf (di:debug-variable-value (car vars) *current-frame*)
			   ,value-var))))
	       ;; If there weren't any exact matches, flame about ambiguity
	       ;; unless all the variables have the same name.
	       ((and (not exact)
		     (find-if-not
		      #'(lambda (v)
			  (string= (di:debug-variable-name v)
				   (di:debug-variable-name (car vars))))
		      (cdr vars)))
		(error "Specification ambiguous:~%~{   ~A~%~}"
		       (mapcar #'di:debug-variable-name
			       (delete-duplicates
				vars :test #'string=
				:key #'di:debug-variable-name))))
chiles's avatar
 
chiles committed
	       ;; All names are the same, so see if the user ID'ed one of them.
	       (id-supplied
		(let ((v (find id vars :key #'di:debug-variable-id)))
		  (unless v
		    (error "Invalid variable ID, ~D, should have been one of ~S."
ram's avatar
ram committed
			   id (mapcar #'di:debug-variable-id vars)))
chiles's avatar
 
chiles committed
		  ,(ecase ref-or-set
		     (:ref
ram's avatar
ram committed
		      '(di:debug-variable-value v *current-frame*))
		     (:set
		      `(setf (di:debug-variable-value v *current-frame*)
			     ,value-var)))))
	       (t
		(error "Specify variable ID to disambiguate ~S.  Use one of ~S."
		       name (mapcar #'di:debug-variable-id vars)))))))))

) ;EVAL-WHEN

;;; VAR -- Public.
;;;
(defun var (name &optional (id 0 id-supplied))
  "Returns a variable's value if possible.  Name is a simple-string or symbol.
   If it is a simple-string, it is an initial substring of the variable's name.
   If name is a symbol, it has the same name and package as the variable whose
   value this function returns.  If the symbol is uninterned, then the variable
   has the same name as the symbol, but it has no package.

   If name is the initial substring of variables with different names, then
   this return no values after displaying the ambiguous names.  If name
   determines multiple variables with the same name, then you must use the
   optional id argument to specify which one you want.  If you left id
   unspecified, then this returns no values after displaying the distinguishing
   id values.

   The result of this function is limited to the availability of variable
   information.  This is SETF'able."
  (define-var-operation :ref))
;;;
(defun (setf var) (value name &optional (id 0 id-supplied))
  (define-var-operation :set value))


ram's avatar
ram committed

;;; ARG -- Public.
;;;
(defun arg (n)
  "Returns the n'th argument's value if possible.  Argument zero is the first
   argument in a frame's default printed representation.  Count keyword/value
   pairs as separate arguments."
  (multiple-value-bind
      (var lambda-var-p)
      (nth-arg n (handler-case (di:debug-function-lambda-list
				(di:frame-debug-function *current-frame*))
		   (di:lambda-list-unavailable ()
		     (error "No argument values are available."))))
    (if lambda-var-p
	(lambda-var-dispatch var (di:frame-code-location *current-frame*)
	  (error "Unused arguments have no values.")
ram's avatar
ram committed
	  (di:debug-variable-value var *current-frame*)
	  (error "Invalid argument value."))
ram's avatar
ram committed
	var)))
ram's avatar
ram committed

;;; NTH-ARG -- Internal.
;;;
;;; This returns the n'th arg as the user sees it from args, the result of
chiles's avatar
 
chiles committed
;;; DI:DEBUG-FUNCTION-LAMBDA-LIST.  If this returns a potential debug-variable
;;; from the lambda-list, then the second value is t.  If this returns a
;;; keyword symbol or a value from a rest arg, then the second value is nil.
;;;
(defun nth-arg (count args)
  (let ((n count))
ram's avatar
ram committed
    (dolist (ele args (error "Argument specification out of range -- ~S." n))
      (lambda-list-element-dispatch ele
chiles's avatar
 
chiles committed
	:required ((if (zerop n) (return (values ele t))))
	:optional ((if (zerop n) (return (values (second ele) t))))
	:keyword ((cond ((zerop n)
			 (return (values (second ele) nil)))
chiles's avatar
 
chiles committed
			((zerop (decf n))
			 (return (values (third ele) t)))))
	:deleted ((if (zerop n) (return (values ele t))))
	:rest ((let ((var (second ele)))
		 (lambda-var-dispatch var
ram's avatar
ram committed
				      (di:frame-code-location *current-frame*)
		   (error "Unused rest-arg before n'th argument.")
chiles's avatar
 
chiles committed
		   (dolist (value
			    (di:debug-variable-value var *current-frame*)
			    (error "Argument specification out of range -- ~S."
				   n))
		     (if (zerop n)
			 (return-from nth-arg (values value nil))
			 (decf n)))
		   (error "Invalid rest-arg before n'th argument.")))))
      (decf n))))



;;;; Debug loop command definition:

(defvar *debug-commands* nil)

;;; DEF-DEBUG-COMMAND -- Internal.
;;;
;;; Interface to *debug-commands*.  No required arguments in args are
;;; permitted.
;;;
(defmacro def-debug-command (name args &rest body)
  (let ((fun-name (intern (concatenate 'simple-string name "-DEBUG-COMMAND"))))
chiles's avatar
 
chiles committed
    `(progn
       (when (assoc ,name *debug-commands* :test #'string=)
	 (setf *debug-commands*
	       (remove ,name *debug-commands* :key #'car :test #'string=)))
       (defun ,fun-name ,args
	 (unless *in-the-debugger*
	   (error "Invoking debugger command while outside the debugger."))
	 ,@body)
       (push (cons ,name #',fun-name) *debug-commands*)
       ',fun-name)))

;;; DEF-DEBUG-COMMAND-ALIAS -- Internal.
;;;
(defun def-debug-command-alias (new-name existing-name)
  (let ((pair (assoc existing-name *debug-commands* :test #'string=)))
    (unless pair (error "Unknown debug command name -- ~S" existing-name))
    (push (cons new-name (cdr pair)) *debug-commands*))
  new-name)

chiles's avatar
 
chiles committed
;;; DEBUG-COMMAND-P -- Internal.
;;;
;;; This takes a symbol and uses its name to find a debugger command, using
;;; initial substring matching.  It returns the command function if form
;;; identifies only one command, but if form is ambiguous, this returns a list
;;; of the command names.  If there are no matches, this returns nil.  Whenever
;;; the loop that looks for a set of possibilities encounters an exact name
;;; match, we return that command function immediately.
;;;
ram's avatar
ram committed
(defun debug-command-p (form &optional other-commands)
  (if (or (symbolp form) (integerp form))
	      (if (symbolp form)
		  (symbol-name form)
		  (format nil "~d" form)))
	     (len (length name))
	     (res nil))