DebugView.st
author Claus Gittinger <cg@exept.de>
Wed, 29 May 1996 13:23:56 +0200
changeset 581 d1a1ae9d49e4
parent 579 d461478b2ac2
child 583 c85ab3ce67f9
permissions -rw-r--r--
removed old non-thread support

"
 COPYRIGHT (c) 1989 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"

StandardSystemView subclass:#DebugView
	instanceVariableNames:'busy haveControl exitAction canContinue contextView codeView
		receiverInspector contextInspector contextArray selectedContext
		catchBlock grabber traceView tracing bigStep skipLineNr
		steppedContextAddress canAbort abortButton terminateButton
		continueButton stepButton nextButton sendButton returnButton
		restartButton exclusive inspecting nChainShown inspectedProcess
		updateProcess stopButton updateButton monitorToggle stepping
		steppedContextLineno stepForReturn actualContext inWrap'
	classVariableNames:'CachedDebugger CachedExclusive OpenDebuggers MoreDebuggingDetail'
	poolDictionaries:''
	category:'Interface-Debugger'
!

!DebugView class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1989 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
!

documentation
"
    this class implements a graphical debugger interface.
    The debugger usually sits on top of the faulting process,
    taking over its event processing. Thus only the 'stopped' process is affected;
    other processes continue to respond to events.

    The one exception is when an error occurs within the dispatcher process
    or in one of the eventhandler processes - in this case, the debugger
    will sit on an exclusive display connection.

    The whole debugging will be changed, once the required process primitives
    are available, which allow control of another processes execution
    (i.e. single-step, restart & return). The setup will be changed then,
    to have the debugger control the debuggee (i.e. two processes)

    See additional information in 'doc/misc/debugger.doc'.

    Notice: the DebugView class caches the last used debugger in a class
    variable. It may happen, that a malfunctioning debugger (for example,
    a halfway destoyed one) is kept there. You will notice this, if a
    debugger comes up without showing any contents. In this case, close
    (or destroy) the broken debugView, and execute
        Debugger newDebugger
    which removes the cached debugger and forces creation of a new one the
    next time. This is a temporary workaround - the debugger will be fixed to
    avoid this problem.

    [author:]
        Claus Gittinger

    [see also:]
        Exception Signal
        Process
"
! !

!DebugView class methodsFor:'initialization'!

reinitialize
    self newDebugger
! !

!DebugView class methodsFor:'instance creation'!

enter
    "another way of entering the debugger"

    ^ self enter:(thisContext sender) withMessage:'Debugger'

    "Debugger enter"
!

enter:aContext
    "enter the debugger on aContext"

    ^ self enter:aContext withMessage:'Debugger'
!

enter:aContext withMessage:aString
    "enter a debugger; if this is a recursive invocation, enter
     a MiniDebugger instead.
     This is the standard way of entering the debugger;
     sent from error- and halt messages."

    |active|

    StepInterruptPending := nil.

    thisContext isRecursive ifTrue:[
        ('DEBUGGER: reentered with: ', aString) errorPrintNL.
        ^ MiniDebugger enterWithMessage:'DEBUGGER: recursive error'.
    ].

    "
     well, it could be a stepping or sending debugger up there;
     in this case, return to it. This happens, when a stepping process
     runs into an error (for example, a halt). In this case, we want the
     stepping debugger to come up again instead of a new one.
    "
    OpenDebuggers notNil ifTrue:[
        active := Processor activeProcess.
        OpenDebuggers do:[:aDebugger |
            aDebugger notNil ifTrue:[
                (aDebugger inspectedProcess == active) ifTrue:[
"/ 'entering stepping debugger again' printNL.
                    aDebugger unstep.
                    aDebugger setLabelFor:aString in:active.
                    ^ aDebugger enter:aContext.
                ]
            ]
        ]
    ].

    ^ self enterUnconditional:aContext withMessage:aString

    "Modified: 1.5.1996 / 15:11:55 / cg"
!

enterUnconditional:aContext withMessage:aString
    "enter a debugger - do not check for recursive invocation"

    |aDebugger|

    StepInterruptPending := nil.
    aDebugger := self new.
    aDebugger setLabelFor:aString in:Processor activeProcess.
    aDebugger enter:aContext.
    ^ nil

    "nil halt"
!

enterWithMessage:aString
    "the standard way of entering the debugger - sent from Objects
     error- and halt messages"

    ^ self enter:(thisContext sender) withMessage:aString

    "Debugger enterWithMessage:'hi there'"
!

new
    "return a new DebugView - return a cached debugger if it already
     exists"

    |debugger|

    "
     need a blocking debugger if no processes or 
     or if its a timing/interrupt process 
     (because otherwise we would not get any events here ...
    "
    Processor activeProcessIsSystemProcess ifTrue:[
	CachedExclusive isNil ifTrue:[
	    debugger := self newExclusive
	] ifFalse:[
	    debugger := CachedExclusive.
	    CachedExclusive := nil.
	].
    ] ifFalse:[
	CachedDebugger isNil ifTrue:[
	    debugger := super new.
	    debugger label:'Debugger'.
	    debugger icon:(Form fromFile:'Debugger.xbm' resolution:100).
	] ifFalse:[
	    debugger := CachedDebugger.
	    CachedDebugger := nil.
	]
    ].
    ^ debugger
!

newExclusive
    "return a debugger for exclusive display access"

    |debugger|

    debugger := super new.
    debugger label:'Debugger'.
    debugger icon:(Form fromFile:'Debugger.xbm' resolution:100).
    debugger exclusive:true.
    ^ debugger
!

openOn:aProcess
    "start a  debugger on aProcess
     (actually not more than a good-looking inspector)"

    |aDebugger label nm|

    aDebugger := super new.
    aDebugger icon:(Form fromFile:'Debugger.xbm' resolution:100).
    aProcess notNil ifTrue:[
	nm := aProcess name.
	nm notNil ifTrue:[
	    nm := (nm contractTo:17) , '-' , aProcess id printString
	] ifFalse:[
	    nm := aProcess id printString
	].
	label := 'Debugger [' , nm , ']'.
    ] ifFalse:[
	label := 'no process'
    ].
    aDebugger label:label.
    aDebugger iconLabel:'Debugger'.
    aDebugger openOn:aProcess.
    ^ nil
! !

!DebugView class methodsFor:'cleanup'!

lowSpaceCleanup 
    "in low memory situations, give up cached debuggers"

    CachedDebugger := nil.
    CachedExclusive := nil.
    OpenDebuggers := nil.

    "
     DebugView lowSpaceCleanup
    "

    "Modified: 18.4.1996 / 16:48:03 / cg"
!

newDebugger
    "force creation of a new debugger"

    CachedDebugger := nil.
    CachedExclusive := nil.
    OpenDebuggers := nil.

    "
     DebugView newDebugger
    "
! !

!DebugView methodsFor:'basic'!

enter
    "enter the debugger - on the sending context"

    |where|

    busy := true.

    where := thisContext.      "enter"
    where := where sender.     "the calling context"
    where notNil ifTrue:[
	(where receiver == DebugView) ifTrue:[
	    where := where sender
	]
	"where is now interrupted methods context"
    ].
    ^ self enter:where
!

enter:aContext
    "enter the debugger - get and display the context, then start an
     exclusive event loop on top of eveything else"

    |con selection m idx retval s|

    busy := true.
    inspecting := false.
    inspectedProcess := Processor activeProcess.
    stepping := false.
    bigStep := false.
    nChainShown := 50.

    "if debugger is entered while a box has grabbed the
     pointer, we must ungrab - otherwise X wont talk to
     us here
    "
    (grabber := device activePointerGrab) notNil ifTrue:[
        device ungrabPointer.
        device ungrabKeyboard.
    ].

    (inspectedProcess suspendedContext isNil 
    or:[Processor isSystemProcess:inspectedProcess]) ifTrue:[
        terminateButton disable.
    ] ifFalse:[
        terminateButton enable.
        abortButton enable.
    ].

    drawableId notNil ifTrue:[
        "
         not the first time - disable buttons & menus
         from previous life
        "
        terminateButton turnOffWithoutRedraw.
        continueButton turnOffWithoutRedraw.
        returnButton turnOffWithoutRedraw.
        restartButton turnOffWithoutRedraw.
        abortButton turnOffWithoutRedraw.
        nextButton turnOffWithoutRedraw.
        stepButton turnOffWithoutRedraw.
        sendButton turnOffWithoutRedraw.

        m := contextView middleButtonMenu.
        m notNil ifTrue:[
            m disableAll:#(showMore skip skipForoReturn inspectContext).
        ]
    ] ifFalse:[
        self iconLabel:'Debugger'.
    ].

    windowGroup isNil ifTrue:[
        windowGroup := WindowGroup new.
        windowGroup addTopView:self.
    ].
    exclusive ifFalse:[
        "/ create a (modal) windowGroup for myself

        windowGroup setModal:true.
    ] ifTrue:[
        "/ create a windowGroup with a synchronous sensor for me

        windowGroup sensor:(SynchronousWindowSensor new).
    ].
    windowGroup setProcess:Processor activeProcess.

    "
     get the walkback list; clear inspectors if we did not come here by single stepping)
    "
    self setContext:aContext releaseInspectors:(exitAction ~~ #step).

    "
     and find the one context to show initially
     - if we came here by a send (single step), its the top context;
     - if we came here by a step (i.e. bigStep), its the top context
       (for ifs and whiles) or the sender (for regular sends).
     - otherwise, we came here by some signal raise, and we are interested
       in the context where the raise actually occured.
    "
    exitAction == #step ifTrue:[
        selection := 1.
        steppedContextAddress notNil ifTrue:[
            "
             if we came here by a big-step, show the method where we are
            "
            (ObjectMemory addressOf:aContext) == steppedContextAddress ifTrue:[
                selection := 1
            ] ifFalse:[
                (ObjectMemory addressOf:aContext sender) == steppedContextAddress ifTrue:[
                    selection := 2
                ]
            ].
            "
             for bigStep, we could also be in a block below the actual method ...
            "
            (aContext home notNil and:[
            (ObjectMemory addressOf:aContext home) == steppedContextAddress]) ifTrue:[
                selection := 1
            ] ifFalse:[
                (aContext sender home notNil and:[
                (ObjectMemory addressOf:aContext sender home) == steppedContextAddress]) ifTrue:[
                    selection := 2
                ]
            ].
        ]
    ] ifFalse:[
        steppedContextAddress isNil ifTrue:[
            "
             preselect a more interesting context, (where halt/raise was ...)
            "
            selection := self interestingContextFrom:aContext.
        ] ifFalse:[
            "
             if we came here by a big-step, show the method where we are
            "
            (ObjectMemory addressOf:aContext) == steppedContextAddress ifTrue:[
                selection := 1
            ] ifFalse:[
                (ObjectMemory addressOf:aContext sender) == steppedContextAddress ifTrue:[
                    selection := 2
                ]
            ]
        ]
    ].

    selection notNil ifTrue:[
        self showSelection:selection.
        contextView setSelection:selection.
        selection > 1 ifTrue:[
            contextView scrollToLine:(selection - 1)
        ]
    ].

    m := contextView middleButtonMenu.
    m notNil ifTrue:[
        canAbort := inspecting or:[Object abortSignal isHandled].
        canAbort ifTrue:[
            abortButton enable.
            m enable:#doAbort.
        ] ifFalse:[
            abortButton disable.
            m disable:#doAbort.
        ].
        exclusive ifTrue:[
            terminateButton disable.
            m disable:#doTerminate.
        ] ifFalse:[
            terminateButton enable.
            m enable:#doTerminate.
        ]
    ].

    "
     drawableId is nil, if this is a new debugger. Then do a realize.
     Otherwise, its probably better to do a map, which shows the
     view at the previous position, without a need for the user to set the
     position again
    "
    drawableId notNil ifTrue:[
        self remap.
    ] ifFalse:[
        self realize.
    ].

    exclusive ifTrue:[
        self showError:'
Debugging system process `' , (inspectedProcess nameOrId) printString , '''.

This is a modal debugger - all event processing is stopped..
Therefore, you cannot interact with other views or 
open any other tools while this debugger is active.

Also, there is no event processing (redraw) for other views.'
    ].

    "
     bring us to the top
    "
    self raise.
    device flush.

    canContinue := true.
    exitAction := nil.

    "
     enter private event handling loop. This is left (and we come back here again)
     when any button was pressed which requires continuation of the debuggee or
     closedown of the debugger.
    "

    [self controlLoop] valueOnUnwindDo:[
        windowGroup notNil ifTrue:[
            windowGroup setProcess:nil.
        ].
        self destroy
    ].

    "
     release all context stuff.
     This is required to avoid keeping references to the debuggees objects
     forever. (since the debugger is reused for faster startup next time)
    "
    contextArray := nil.
    codeView acceptAction:nil.
    contextView contents:nil.

    (exitAction ~~ #step) ifTrue:[
        receiverInspector release.
        contextInspector release.

        self unmap.
        device flush.

        (exitAction == #abort) ifTrue:[
            self cacheMyself.
            "
             have to catch errors occuring in unwind-blocks
            "
            ErrorSignal handle:[:ex |
                'ignored error while unwinding: ' errorPrint.
                ex errorString errorPrintNL.
                ex proceed
            ] do:[
                Object abortSignal raise.
            ].
            'abort failed' errorPrintNL
        ].

        (exitAction == #return) ifTrue:[
            selectedContext notNil ifTrue:[
                "
                 if there is a selection in the codeView,
                 evaluate it and use the result as return value
                "
"/ disabled for now, there is almost always a selection (the current line)
"/ and that is syntactically incorrect ...
"/ ... leading to a popup warning from the codeView
"/
"/                codeView hasSelection ifTrue:[
"/                    s := codeView selection asString.
"/                    Object errorSignal handle:[:ex |
"/                        'DEBUGGER: error - returning nil' printNL.
"/                        retval := nil.
"/                        ex return
"/                    ] do:[
"/                        retval := codeView doItAction value:s.
"/                    ].
"/                ].

                con := selectedContext.
                self cacheMyself.
                "
                 have to catch errors occuring in unwind-blocks
                "
                Object errorSignal handle:[:ex |
                    'ignored error while unwinding: ' errorPrint.
                    ex errorString errorPrintNL.
                    ex proceed
                ] do:[
                    con unwind:retval.
                ].
                'cannot return from selected context' errorPrintNL
            ]
        ].

        (exitAction == #restart) ifTrue:[
            selectedContext notNil ifTrue:[
                con := selectedContext.
                self cacheMyself.
                "
                 have to catch errors occuring in unwind-blocks
                "
                Object errorSignal handle:[:ex |
                    'ignored error while unwinding: ' errorPrint.
                    ex errorString errorPrintNL.
                    ex proceed
                ] do:[
                    con unwindAndRestart.
                ].
                'cannot restart selected context' errorPrintNL
            ]
        ].

        (exitAction == #quickTerminate) ifTrue:[
            self cacheMyself.
            Processor activeProcess terminateNoSignal
        ].

        (exitAction == #terminate) ifTrue:[
            self cacheMyself.
            "
             have to catch errors occuring in unwind-blocks
            "
            Object errorSignal handle:[:ex |
                'ignored error while unwinding: ' errorPrint.
                ex errorString errorPrintNL.
                ex proceed
            ] do:[
                Processor activeProcess terminate.
            ].
            'cannot terminate process' errorPrintNL
        ]
    ].

    selectedContext := actualContext := nil.

    grabber notNil ifTrue:[
        device grabPointerInView:grabber.
        grabber := nil.
    ].

    (exitAction == #step) ifTrue:[
        "
         schedule another stepInterrupt
         - must enter myself into the collection of open debuggers,
           in case the stepping process comes back again via a halt or signal
           before the step is finished. In this case, the stepping debugger should
           come up (instead of a new one)
         - must flush caches since optimized methods not always
           look for pending interrupts
        "
        OpenDebuggers isNil ifTrue:[
            OpenDebuggers := WeakArray with:self
        ] ifFalse:[
            (OpenDebuggers includes:self) ifFalse:[
                idx := OpenDebuggers identityIndexOf:nil.
                idx ~~ 0 ifTrue:[
                    OpenDebuggers at:idx put:self
                ] ifFalse:[
                    OpenDebuggers := OpenDebuggers copyWith:self
                ]
            ]
        ].
        self label:'single stepping - please wait ...'.
        stepping := true.

        ObjectMemory stepInterruptHandler:self.
        stepForReturn == true ifFalse:[
            Context singleStepInterruptRequest isHandled ifTrue:[
                Context singleStepInterruptRequest raise
            ] ifFalse:[
                ObjectMemory flushInlineCaches.
                StepInterruptPending := 1.
                InterruptPending := 1.
                InStepInterrupt := nil
            ]
        ]
    ] ifFalse:[
        OpenDebuggers notNil ifTrue:[
            idx := OpenDebuggers identityIndexOf:self.
            idx ~~ 0 ifTrue:[
                OpenDebuggers at:idx put:nil
            ]
        ].
        self cacheMyself.
    ]

    "Created: 24.11.1995 / 19:52:54 / cg"
    "Modified: 3.5.1996 / 23:58:16 / stefan"
    "Modified: 28.5.1996 / 18:42:23 / cg"
!

openOn:aProcess
    "enter the debugger on a process - 
     in this case, we are just inspecting the context chain of the process,
     not running on top of the debugged process, but as a separate
     one. (think of it as an inspector showing more detail, and offering
     some more control operations)"

    |bpanel dummy|

    busy := true.
    bigStep := false.
    inspecting := true.
    inspectedProcess := aProcess.
    nChainShown := 50.

    bpanel := abortButton superView.

    stopButton := Button new.
    stopButton label:(resources at:'stop');
	       action:[self doStop].
    bpanel addSubView:stopButton after:continueButton.

    dummy := View extent:(10 @ 5) in:bpanel.
    dummy borderWidth:0; level:0.

"/    stepButton destroy.
"/    sendButton destroy.

    updateButton := Button
			label:(resources at:'update')
			action:[self updateContext]
			in:bpanel.
    monitorToggle := Toggle in:bpanel.
    monitorToggle label:(resources at:'monitor').
    monitorToggle pressAction:[self autoUpdateOn].
    monitorToggle releaseAction:[self autoUpdateOff].

    "can only look into process - context chain is not active"
    canContinue := true.

    terminateButton enable.
    abortButton enable.

    sendButton disable.
    stepButton disable.
    nextButton disable.
"/    continueButton disable.
"/    returnButton disable.
"/    restartButton disable.

    aProcess isNil ifTrue:[
	terminateButton disable.
	abortButton disable.
	continueButton disable.
	returnButton disable.
	restartButton disable.
    ] ifFalse:[
	(aProcess suspendedContext isNil 
	or:[Processor isSystemProcess:aProcess]) ifTrue:[
	    terminateButton disable.
	].

	self setContext:aProcess suspendedContext.

	catchBlock := [
	    catchBlock := nil.
	    contextArray := nil.
	    selectedContext := actualContext := nil.
	    (exitAction == #terminate) ifTrue:[
		aProcess terminate.
	    ].
	    (exitAction == #quickTerminate) ifTrue:[
		aProcess terminateNoSignal.
	    ].
	    super destroy
	].
    ].
    self open

    "Modified: 22.12.1995 / 23:30:37 / cg"
! !

!DebugView methodsFor:'help'!

helpTextFor:aComponent
    |s|

    aComponent == abortButton ifTrue:[
	s := 'HELP_ABORT'
    ].
    aComponent == terminateButton ifTrue:[
	s := 'HELP_TERMINATE'
    ].
    aComponent == continueButton ifTrue:[
	s := 'HELP_CONTINUE'
    ].
    aComponent == stepButton ifTrue:[
	s := 'HELP_STEP'
    ].
    aComponent == nextButton ifTrue:[
	s := 'HELP_NEXT'
    ].
    aComponent == stepButton ifTrue:[
	s := 'HELP_STEP'
    ].
    aComponent == sendButton ifTrue:[
	s := 'HELP_SEND'
    ].
    aComponent == returnButton ifTrue:[
	s := 'HELP_RETURN'
    ].
    aComponent == restartButton ifTrue:[
	s := 'HELP_RESTART'
    ].
    aComponent == contextView ifTrue:[
	s := 'HELP_WALKBACK'
    ].
    aComponent == codeView ifTrue:[
	s := 'HELP_CODEVIEW'
    ].
    aComponent == monitorToggle ifTrue:[
	s := 'HELP_MONITOR'
    ].
    aComponent == updateButton ifTrue:[
	s := 'HELP_UPDATE'
    ].
    aComponent == stopButton ifTrue:[
	s := 'HELP_STOP'
    ].
    (aComponent isSubViewOf:receiverInspector) ifTrue:[
	s := 'HELP_REC_INSP'
    ].
    (aComponent isSubViewOf:contextInspector) ifTrue:[
	s := 'HELP_CON_INSP'
    ].

    s notNil ifTrue:[
	^ resources string:s
    ].
    ^ nil

    "Modified: 29.8.1995 / 23:38:54 / claus"
! !

!DebugView methodsFor:'initialization'!

addToCurrentProject
    "ignored here"

    ^ self
!

createOnTop
    ^ false "true"
!

initialize
    |v panel hpanel bpanel separator|

    super initialize.

    font := font on:device.

    busy := false.
    exclusive := false.
    inspecting := false.
    exitAction := nil.
    bigStep := false.
    canContinue := false.
    canAbort := false.

    bpanel := HorizontalPanelView
"/                        origin:(0.0 @ 0.0)
"/                        extent:(1.0 @ (font height * 2))
                            in:self.
    bpanel horizontalLayout:#leftSpace.
    bpanel verticalSpace:ViewSpacing // 2.

    terminateButton := Button
                        label:(resources at:'terminate')
                        action:[terminateButton turnOffWithoutRedraw. self doTerminate]
                        in:bpanel.
    separator := View extent:(10 @ 5) in:bpanel.
    separator borderWidth:0; level:0.

    abortButton := Button
                        label:(resources at:'abort')
                        action:[abortButton turnOffWithoutRedraw. self doAbort]
                        in:bpanel.
    returnButton := Button
                        label:(resources at:'return')
                        action:[returnButton turnOff. self doReturn]
                        in:bpanel.

    restartButton := Button
                        label:(resources at:'restart')
                        action:[restartButton turnOff. self doRestart]
                        in:bpanel.

    separator := View extent:(10 @ 5) in:bpanel.
    separator borderWidth:0; level:0.

    continueButton := Button
                        label:(resources at:'continue')
                        action:[continueButton turnOffWithoutRedraw. self doContinue]
                        in:bpanel.

    separator := View extent:(10 @ 5) in:bpanel.
    separator borderWidth:0; level:0.

    nextButton := Button
                        label:(resources at:'next')
                        action:[stepButton turnOff. self doNext]
                        in:bpanel.
    stepButton := Button
                        label:(resources at:'step')
                        action:[stepButton turnOff. self doStep]
                        in:bpanel.
    sendButton := Button
                        label:(resources at:'send')
                        action:[sendButton turnOff. self doSend]
                        in:bpanel.

    bpanel origin:(0.0 @ 0.0)
           extent:(1.0 @ (bpanel preferredExtent y)).

    panel := VariableVerticalPanel
                        origin:(0.0 @ bpanel height)
                        corner:(1.0 @ 1.0)
                            in:self.

    v := ScrollableView for:SelectionInListView in:panel.
    v origin:(0.0 @ 0.0) corner:(1.0 @ 0.25).

    contextView := v scrolledView.
    contextView action:[:lineNr | self showSelection:lineNr].
    contextView doubleClickAction:[:line | self browse].

    v := ScrollableView for:CodeView in:panel.
    v origin:(0.0 @ 0.25) corner:(1.0 @ 0.75).

    codeView := v scrolledView.

    hpanel := VariableHorizontalPanel in:panel.
    hpanel origin:(0.0 @ 0.75) corner:(1.0 @ 1.0).

    receiverInspector := InspectorView
                                origin:(0.0 @ 0.0) corner:(0.5 @ 1.0)
                                    in:hpanel.

    contextInspector := ContextInspectorView
                                origin:(0.5 @ 0.0) corner:(1.0 @ 1.0)
                                    in:hpanel

    "Modified: 20.4.1996 / 13:34:52 / cg"
!

initializeMiddleButtonMenu
    |labels selectors m|

    exclusive ifTrue:[
        labels := resources array:#(
                                    'show more'
                                    '-'
                                    'remove breakpoint'
                                    'remove all trace & breakpoints'
                                    '-'
                                    'copy walkback text'
                                    '-'
                                    'quickTerminate'
                                    '='
                                    'exit smalltalk (no confirmation)'
                                  ).
        selectors := #(
                                 showMore
                                 nil
                                 removeBreakpoint
                                 removeAllBreakpoints
                                 nil
                                 copyWalkbackText
                                 nil
                                 quickTerminate
                                 nil
                                 exit
                      )
    ] ifFalse:[
        labels := resources array:#(
                                    'show more'
                                    '-'
                                    'skip'
                                    '-'
"
                                    'continue'
                                    'terminate'
                                    'abort'
                                    '-'
                                    'step'
                                    'send'
                                    '-'
                                    'return'
                                    'restart'
                                    '-'
"
                                    'remove breakpoint'
                                    'remove all trace & breakpoints'
                                    '-'
                                    'browse'
                                    'browse class'
                                    'browse class hierarchy'
                                    'browse full class protocol'
                                    'implementors'
                                    'senders'
                                    '-'
                                    'inspect context'
                                    'copy walkback text'
                                    '-'
                                    'quickTerminate'
                                    '='
                                    'exit smalltalk (no confirmation)'
                              ).

        selectors := #(
                                         showMore
                                         nil
                                         skip
                                         nil
"
                                         doContinue
                                         doTerminate
                                         doAbort
                                         nil
                                         doStep
                                         doSend
                                         nil
                                         doReturn
                                         doRestart
                                         nil
"
                                         removeBreakpoint
                                         removeAllBreakpoints
                                         nil
                                         browse
                                         browseClass
                                         browseClassHierarchy
                                         browseFullClassProtocol
                                         implementors
                                         senders
                                         nil
                                         inspectContext
                                         copyWalkbackText
                                         nil
                                         quickTerminate
                                         nil
                                         exit
        ).
    ].

    m := PopUpMenu 
                labels:labels
             selectors:selectors
              receiver:self
                   for:contextView.

    contextView middleButtonMenu:m. 

    inspecting ifTrue:[
        m notNil ifTrue:[
            m disableAll:#(doTraceStep removeBreakpoint browse browseClass
                           browseClassHierarchy browseFullClassProtocol
                           implementors senders inspectContext skip).
        ].
    ]

    "Modified: 27.2.1996 / 14:41:53 / cg"
!

realize
    super realize.
"/    exclusive ifTrue:[
"/        windowGroup := nil
"/    ].

    inspecting ifTrue:[
	inspectedProcess notNil ifTrue:[
	    "
	     set prio somewhat higher (by 2, to allow walkBack-update process
	     to run between mine and the debugged processes prio)
	    "
	    Processor activeProcess 
		priority:(inspectedProcess priority + 2 min:16).
	]
    ]
!

setLabelFor:aMessage in:aProcess
    |l nm|

    l := aMessage , ' ('.
    nm := aProcess name.
    nm notNil ifTrue:[
	l := l , (nm contractTo:17) , ''.
    ].
    l := l , '[' , aProcess id printString , '])'.
    self label:l.
! !

!DebugView methodsFor:'interrupt handling'!

stepInterrupt
    |where here s isWrap method lastWrappedConAddr wrappedMethod inBlock left ignore|

    "/
    "/ should no longer happen
    "/
    stepForReturn == true ifTrue:[
        self enter:thisContext sender.
        ^ self
    ].

    Processor activeProcess ~~ inspectedProcess ifTrue:[
        'stray step interrupt' errorPrintNL.
        ^ self
    ].

    "
     kludge to hide breakpoint wrappers in the context list: 
         check if we are in a wrapper methods hidden setup-sequence
         if so, ignore the interrupt and continue single sending
    "
    here := thisContext.        "stepInterrupt"
    here := here sender.        "the interrupted context"  

"/ '*******' printNL.
"/ 'here in ' print.
"/  ((ObjectMemory addressOf:here) printStringRadix:16)print. '' printNL.

    where := here.
    isWrap := false.
    left := false.

    inWrap ifTrue:[
        wrappedMethod := nil.
        5 timesRepeat:[
"/ where selector printNL.
            (where notNil and:[where isBlockContext not]) ifTrue:[
                method := where method.
                (method notNil and:[method isWrapped]) ifTrue:[
                    "
                     in a wrapper method
                    "
                    wrappedMethod ~~ method ifTrue:[
                        wrappedMethod := method.
                        lastWrappedConAddr := ObjectMemory addressOf:where.
                        where sender receiver == method originalMethod ifFalse:[
                            isWrap := true.
                        ]
                    ] ifFalse:[
                        (ObjectMemory addressOf:where) == steppedContextAddress ifTrue:[
"/ 'change stepCon from: ' print.
"/ (steppedContextAddress printStringRadix:16)print.
"/ ' to: ' print.
"/ (lastWrappedConAddr printStringRadix:16)printNL.

                            inWrap := false.
                            steppedContextAddress := lastWrappedConAddr
                        ]
                    ]
                ].
                where := where sender
            ]
        ].
    ].

    isWrap ifTrue:[
"/ 'ignore wrap' printNL.
"/ ' ' printNL.
        "
          ignore, while in wrappers hidden setup
        "
        where := nil. here := nil.
        ObjectMemory flushInlineCaches.
        StepInterruptPending := 1.
        InterruptPending := 1.
        InStepInterrupt := nil.
        ^ nil
    ].

    inBlock := false.

    "
     is this for a send or a step/next ?
    "
    bigStep ifTrue:[
        "
         a step or next - ignore all contexts below the interesting one
        "
        where := here.      "the interrupted context"

        where home notNil ifTrue:[
            "/
            "/ in a block called by 'our' context ?
            "/
            (ObjectMemory addressOf:where home) == steppedContextAddress ifTrue:[
"/ '*block*' printNL.
                inBlock := true
            ]
        ].

        (ObjectMemory addressOf:where) == steppedContextAddress ifFalse:[
            where := where sender.

            where home notNil ifTrue:[
                (ObjectMemory addressOf:where home) == steppedContextAddress ifTrue:[
"/ '*block*' printNL.
                    inBlock := true.
                ]
            ].

"/ 'looking for ' print.
"/  (steppedContextAddress printStringRadix:16)print. '' printNL.

            (ObjectMemory addressOf:where) == steppedContextAddress ifFalse:[
                "
                 check if we are in a context below steppedContext
                 (i.e. if steppedContext can be reached from
                  interrupted context. Not using context-ref but its
                  address to avoid creation of many useless contexts.)
                "
                inBlock ifFalse:[
                    [where notNil] whileTrue:[
"/  ((ObjectMemory addressOf:where) printStringRadix:16)print. ' ' print.
"/  where selector printNL.
                        (ObjectMemory addressOf:where) == steppedContextAddress ifTrue:[
"/ 'found it - below; ignore' printNL.
                            "
                             found the interesting context somwehere up in the
                             chain. We seem to be still below the interesting one ...
                            "
                            tracing == true ifTrue:[
                                here printString printCR
                            ].
                            where := nil. here := nil.
                            "
                              yes, a context below
                              - continue and schedule another stepInterrupt.
                              Must flush caches since optimized methods not always
                              look for pending interrupts
                            "
                            ObjectMemory flushInlineCaches.
                            StepInterruptPending := 1.
                            InterruptPending := 1.
                            InStepInterrupt := nil.
                            ^ nil
                        ].
                        where := where sender
                    ].
                    s := 'left stepped method'.
                    left := true.
                ].
            ] ifTrue:[
"/ 'found it right in sender' printNL.
                s := 'after step'
            ].
        ] ifTrue:[
"/ 'found it right away' printNL.
            s := 'after step'
        ].
    ] ifFalse:[
"/ ' send' printNL.
        "
         a send
        "
        steppedContextAddress := nil.
        s := 'after send'
    ].

    inBlock ifTrue:[
"/ 'inBlock' printNL.
        s := 'in block'.
    ].

"/    where notNil ifTrue:[
"/        '(' print. steppedContextLineno print. ') ' print.
"/        where print.
"/        '[' print. where lineNumber print. ']' printNL.
"/    ].

    ignore := false.

    (bigStep 
    and:[steppedContextLineno notNil 
    and:[where notNil 
    and:[where lineNumber == steppedContextLineno]]]) ifTrue:[
"/ 'same line - ignored' printNL.
        ignore := true
    ].

    (left not 
    and:[skipLineNr notNil 
    and:[where lineNumber ~~ skipLineNr]]) ifTrue:[
"/ 'skip (' print. skipLineNr print. ' unreached - ignored' printNL.
        ignore := true
    ].

    ignore ifTrue:[
"/' ' printNL.
        where := nil. here := nil.
        "
         yes, a context below
          - continue and schedule another stepInterrupt.
          Must flush caches since optimized methods not always
          look for pending interrupts
        "
        ObjectMemory flushInlineCaches.
        StepInterruptPending := 1.
        InterruptPending := 1.
        InStepInterrupt := nil.
        ^ nil
    ].

"/ ' ' printNL.

    name := Processor activeProcess nameOrId.
    self label:(s , ' (process: ' , name , ')').

    tracing := false.
    bigStep := false.

    "release refs to context"
    where := nil. here := nil.
    self enter:thisContext sender

    "Modified: 20.5.1996 / 10:27:24 / cg"
! !

!DebugView methodsFor:'menu / button actions'!

autoUpdateOff
    "stop the update process"

    updateProcess notNil ifTrue:[
	monitorToggle lampColor:(Color yellow).
	updateProcess terminate.
	updateProcess := nil
    ]
!

autoUpdateOn
    "fork a subprocess which updates the contextList in regular intervals"

    updateProcess isNil ifTrue:[
	updateProcess := 
	    [
		[true] whileTrue:[
		    monitorToggle showLamp ifTrue:[
			monitorToggle lampColor:(Color yellow).
		    ] ifFalse:[
			monitorToggle activeForegroundColor:Color black.
		    ].
		    (Delay forSeconds:0.25) wait.
		    self updateContext.
		    monitorToggle showLamp ifTrue:[
			monitorToggle lampColor:(Color red).
		    ] ifFalse:[
			monitorToggle activeForegroundColor:Color red.
		    ].
		    (Delay forSeconds:0.25) wait.
		    self updateContext.
		]
	    ] forkAt:(Processor activePriority - 1)
    ]

!

browse
    |w cls|

    w := selectedContext method who.
    cls := w at:1.
"/ cls printCR.
    cls browserClass openInClass:cls selector:(w at:2).

    "Created: 22.11.1995 / 21:27:01 / cg"
    "Modified: 20.5.1996 / 10:28:16 / cg"
!

browseClass
    |w cls|

    w := selectedContext method who.
    cls := w at:1.
    cls browserClass browseClass:cls

    "Modified: 3.5.1996 / 12:37:59 / cg"
!

browseClassHierarchy
    |w cls|

    w := selectedContext method who.
    cls := w at:1.
    cls browserClass browseClassHierarchy:cls.

    "Modified: 3.5.1996 / 12:38:17 / cg"
!

browseFullClassProtocol
    |w cls|

    w := selectedContext method who.
    cls := w at:1.
    cls browserClass browseFullClassProtocol:cls.

    "Modified: 3.5.1996 / 12:38:30 / cg"
!

copyWalkbackText
    "place the contents of the walkback view into the copy-paste buffer.
     This allows pasting it into some other view for printing ..."

    self setTextSelection:(contextArray collect:[:con | con fullPrintString]) asStringCollection

    "Modified: 28.8.1995 / 15:31:59 / claus"
!

doAbort
    "abort - send Object>>abortSignal, which is usually cought
     at save places (for example: in the event loop) and returns back
     from whatever the process is doing, but does not terminate it."

    inspecting ifTrue:[
        inspectedProcess isDead ifTrue:[
            self showTerminated.
            ^ self
        ].
        (Object abortSignal isHandledIn:inspectedProcess suspendedContext) ifFalse:[
            self showError:'** the process does not handle the abort signal **'
        ] ifTrue:[
            self interruptProcessWith:[Object abortSignal raise].
        ].
        ^ self
    ].

    steppedContextAddress := nil.
    haveControl := false.
    exitAction := #abort.

    "exit private event-loop"
    catchBlock notNil ifTrue:[
        abortButton turnOff.
        catchBlock value.

        "/ not reached
        'DEBUGGER: oops, abort failed' errorPrintNL.
    ].

    ^ self.

    "Modified: 29.5.1996 / 13:18:39 / cg"
!

doContinue
    "continue from menu"

    inspecting ifTrue:[
        self processPerform:#resume.
        ^ self
    ].
    canContinue ifTrue:[
        steppedContextAddress := nil.
        tracing := false.
        haveControl := false.
        exitAction := #continue.

        "exit private event-loop"
        catchBlock notNil ifTrue:[catchBlock value].

        "/ not reached.
        'DEBUGGER: oops, continue failed' errorPrintNL.
        continueButton turnOff.

    ] ifFalse:[
        inspecting ifFalse:[
            'resuming top context' errorPrintNL.
            self showSelection:1.
            self doReturn
        ]
    ]

    "Modified: 29.5.1996 / 13:18:29 / cg"
!

doNext
    "skip for next source-code line"

    self doStep:nil
!

doNoTrace
    traceView notNil ifTrue:[
	traceView topView destroy.
	traceView := nil.
    ].
    tracing := false
!

doRestart
    "restart - the selected context will be restarted"

    inspecting ifTrue:[
        selectedContext isNil ifTrue:[
            ^ self showError:'** select a context first **'
        ].
        self interruptProcessWith:[selectedContext unwindAndRestart].
        ^ self
    ].

    steppedContextAddress := nil.
    haveControl := false.
    exitAction := #restart.

    "exit private event-loop"
    catchBlock notNil ifTrue:[catchBlock value].

    "/ not reached
    'DEBUGGER: oops, restart failed' errorPrintNL.
    restartButton turnOff.

    "Modified: 29.5.1996 / 13:18:55 / cg"
!

doReturn
    "return - the selected context will do a ^nil"

    inspecting ifTrue:[
        selectedContext isNil ifTrue:[
            ^ self showError:'** select a context first **'
        ].
        self interruptProcessWith:[selectedContext unwind].
        ^ self
    ].

    steppedContextAddress := nil.
    haveControl := false.
    exitAction := #return.

    "exit private event-loop"
    catchBlock notNil ifTrue:[catchBlock value].

    "/ not reached
    'DEBUGGER: oops, return failed' errorPrintNL.
    returnButton turnOff.

    "Modified: 29.5.1996 / 13:19:12 / cg"
!

doSend
    "single send; reenter with next message send"

    inspecting ifTrue:[^ self].

    canContinue ifTrue:[
        steppedContextAddress := nil.
        haveControl := false.
        exitAction := #step.

        "exit private event-loop"
        catchBlock notNil ifTrue:[catchBlock value].

        "/ not reached
        'DEBUGGER: oops, send failed' errorPrintNL.
        sendButton turnOff.
    ]

    "Modified: 29.5.1996 / 13:19:23 / cg"
!

doStep
    "skip for next send in selected method"

    self doStep:-1 
!

doStep:lineNr
    "step until we pass lineNr (if nonNil) or to next line (if nil)
     or to next send (if -1)"

    |con method|

    inspecting ifTrue:[^ self].

    canContinue ifTrue:[
        selectedContext notNil ifTrue:[
            con := selectedContext.
            steppedContextLineno := actualContext lineNumber.
        ] ifFalse:[
            con := contextArray at:2.
            steppedContextLineno := con lineNumber.
        ].
        skipLineNr := lineNr.

        lineNr == -1 ifTrue:[
            steppedContextLineno := skipLineNr := nil.
        ].

        steppedContextAddress := ObjectMemory addressOf:con.
        "
         if we step in a wrapped method,
         prepare to skip the prolog ...
        "
"/ ' step con:' print. steppedContextAddress printHex. ' ' printNL.
        inWrap := false.
        method := con method.
        (method notNil and:[method isWrapped]) ifTrue:[
            inWrap := true
        ].

        con := nil.
        bigStep := true.
        haveControl := false.
        exitAction := #step.

        "exit private event-loop"
        catchBlock notNil ifTrue:[catchBlock value].

        "/ not reached
        'DEBUGGER: oops, step failed' errorPrintNL.
        stepButton turnOff.
        nextButton turnOff.
        sendButton turnOff.
    ]

    "Modified: 29.5.1996 / 13:19:38 / cg"
!

doStop
    "stop the process (if its running, otherwise this is a no-op)"

    inspecting ifTrue:[
	self processPerform:#stop.
	^ self
    ].
!

doTerminate
    "terminate - the process has a chance for cleanup"

    inspecting ifTrue:[
        self processPerform:#terminate.
        ^ self
    ].

    steppedContextAddress := nil.
    haveControl := false.
    exitAction := #terminate. 

    "exit private event-loop"
    catchBlock notNil ifTrue:[catchBlock value].

    "/ not reached (normally)
    inspecting ifFalse:[
        'DEBUGGER: oops, terminate failed' errorPrintNL.
        self warn:'terminate failed'.
    ].
    terminateButton turnOff.

    "Modified: 29.5.1996 / 13:19:57 / cg"
!

doTrace
    "tracing - not really implemented ..."

    self warn:'this function is not yet implemented'.

"/    |v b|
"/
"/    traceView isNil ifTrue:[
"/        v := StandardSystemView on:Display.
"/        v label:'Debugger-Trace'.
"/        v icon:icon.
"/
"/        b := Button label:'untrace' in:v.
"/        b origin:(0 @ 0) extent:(1.0 @ (b height)).
"/        b action:[
"/            StepInterruptPending := nil.
"/            tracing := false.
"/            v unrealize.
"/            traceView := nil
"/        ].
"/        traceView := ScrollableView for:TextCollector in:v.
"/        traceView origin:(0 @ (b height))
"/                  extent:[v width @ (v height - b height)]
"/    ].
"/    v realize.
"/
"/    tracing := true.
!

doTraceStep
    "tracestep - not implemented yet"

    canContinue ifTrue:[
	tracing := true.
	self doStep
    ]
!

exit
    "exit from menu: immediate exit from smalltalk"

    OperatingSystem exit
!

implementors
    "open a browser on the implementors"

    selectedContext isNil ifTrue:[
	^ self showError:'** select a context first **'
    ].
    SystemBrowser browseImplementorsOf:selectedContext selector.
!

inspectContext
    "launch an inspector on the currently selected context"

    contextView selection notNil ifTrue:[
	(contextView selectionValue startsWith:'**') ifFalse:[
	    (contextArray at:(contextView selection)) inspect.
	]
    ]
!

quickTerminate
    "quick terminate - the process will get no chance for cleanup actions"

    inspecting ifTrue:[
        self processPerform:#terminateNoSignal.
        ^ self
    ].

    steppedContextAddress := nil.
    haveControl := false.
    exitAction := #quickTerminate.

    "exit private event-loop"
    catchBlock notNil ifTrue:[catchBlock value].

    "/ not reached (normally)
    inspecting ifFalse:[
        'DEBUGGER: oops, terminate failed' errorPrintNL.
        self warn:'terminate failed'.
    ].
    terminateButton turnOff.

    "Modified: 29.5.1996 / 13:20:14 / cg"
!

removeAllBreakpoints
    "remove all trace & breakpoints - if any"

    MessageTracer unwrapAllMethods
!

removeBreakpoint
    "remove breakpoint on the selected contexts method - if any"

    |implementorClass method|

    selectedContext isNil ifTrue:[
	^ self showError:'** select a context first **'
    ].

    implementorClass := selectedContext methodClass. 
    implementorClass notNil ifTrue:[
	method := implementorClass compiledMethodAt:selectedContext selector.
	(method notNil and:[method isWrapped]) ifTrue:[
	    MessageTracer unwrapMethod:method
	]
    ].
    contextView middleButtonMenu disable:#removeBreakpoint.
!

senders
    "open a browser on the senders"

    selectedContext isNil ifTrue:[
	^ self showError:'** select a context first **'
    ].
    SystemBrowser browseAllCallsOn:selectedContext selector.
!

showMore
    "double number of contexts shown"

    |oldSelection con|

    contextArray notNil ifTrue:[
        oldSelection := contextView selection.
        nChainShown := nChainShown * 2.
        con := contextArray at:1.
        contextArray at:1 put:nil.
        self setContext:con.
        contextView setSelection:oldSelection.
    ]

    "Modified: 25.5.1996 / 12:26:55 / cg"
!

skip
    "skip for cursor line in selected method"

    self doStep:codeView cursorLine.
! !

!DebugView methodsFor:'private'!

busy
    ^ busy
!

cacheMyself
    "remember myself for next debug session"

    "caching the last debugger will make the next debugger appear
     faster, since no resources have to be allocated in the display.
     We have to be careful to release all refs to the debuggee, though.
     Otherwise, the GC will not be able to release it"

    windowGroup notNil ifTrue:[
	windowGroup setProcess:nil.
    ].

    busy := false.
    codeView acceptAction:nil.
    codeView doItAction:nil.
    codeView contents:nil.
    receiverInspector release.
    contextInspector release.
    inspectedProcess := nil.
    exitAction := nil.
    contextArray := nil.
    selectedContext := actualContext := nil.
    catchBlock := nil.
    grabber := nil.
    self autoUpdateOff.

    exclusive ifTrue:[CachedExclusive := self] ifFalse:[CachedDebugger := self].
!

exclusive:aBoolean
    exclusive := aBoolean
!

inspectedProcess 
    ^ inspectedProcess 
!

interestingContextFrom:aContext
    "return an interesting contexts offset, or nil.
     This is the context initially shown in the walkback.
     We move up the calling chain, skipping all intermediate Signal
     and Exception contexts, to present the context in which the error
     actually occured.
     Just for your convenience :-)"

    |c found offset sel prev ex|

    "somewhere, at the bottom, there must be a raise ..."

    c := aContext.
    1 to:5 do:[:i |
	c isNil ifTrue:[^ 1 "^ nil"].
	sel := c selector.
	(sel == #raise) ifTrue:[
	    (c receiver isKindOf:Exception) ifTrue:[
		ex := c receiver.
		offset := i.
		found := c
	    ] ifFalse:[
		(c receiver isKindOf:Signal) ifTrue:[
		    offset := i.
		    found := c
		]
	    ]
	].
	c := c sender.
    ].

    "
     if this is a noHandler exception, skip forward
     to the erronous context
    "
    ex notNil ifTrue:[
	ex signal == Signal noHandlerSignal ifTrue:[
	    c := ex suspendedContext
	]
    ].

    (c := found) isNil ifTrue:[^ 1].

    "
     got it; move up, skipping all intermediate Signal and
     Exception contexts
    "
    prev := nil.
    [   
	((c receiver isSignal)
	or:[(c receiver isKindOf:Exception)])
    ] whileTrue:[
	prev := c.
	(c := c sender) isNil ifTrue:[^ offset].
	offset := offset + 1.
    ].

    "
     now, we are one above the raise
    "

    "
     if the sender-method of the raise is one of objects error methods ...
    "
    ( #( halt halt: 
	 error error: 
	 doesNotUnderstand: 
	 subclassResponsibility 
	 primitiveFailed) includes:c selector) 
    ifTrue:[
	c selector == #doesNotUnderstand: ifTrue:[
	    "
	     one more up, to get to the originating context
	    "
	    (c := c sender) isNil ifTrue:[^ offset].
	    offset := offset + 1.
	].
	(c := c sender) isNil ifTrue:[^ offset].
	offset := offset + 1.
    ] ifFalse:[
	"
	 ok, got the raise - if its a BreakPoint, look for the sender
	"
	(MessageTracer notNil and:[prev receiver == MessageTracer breakpointSignal]) ifTrue:[
	    offset := offset + 1
	].
    ].

    ^ offset

    "Created: 10.12.1995 / 13:55:21 / cg"
!

interruptProcessWith:aBlock
    "let inspected process do something, then update the context list"

    inspectedProcess isDead ifTrue:[
	self showTerminated.
	^ self
    ].
    inspectedProcess interruptWith:aBlock.
    "
     give the process a chance to run, then update
    "
    (Delay forSeconds:0.2) wait.
    self setContext:(inspectedProcess suspendedContext).
!

processPerform:aMessage
    "do something, then update the context list"

    inspectedProcess isDead ifTrue:[
	self showTerminated.
	^ self
    ].
    inspectedProcess perform:aMessage.
    "
     give the process a chance to run, then update
    "
    (Delay forSeconds:0.2) wait.
    self setContext:(inspectedProcess suspendedContext).
!

setContext:aContext
    "show calling chain from aContext in the walk-back listview"

    self setContext:aContext releaseInspectors:true

    "Modified: 14.12.1995 / 19:10:51 / cg"
!

setContext:aContext releaseInspectors:releaseInspectors
    "show calling chain from aContext in the walk-back listview"

    |con text method caller caller2 m count|

    (contextArray notNil and:[aContext == (contextArray at:1)]) ifTrue:[
	"no change"
	^ false
    ].

    m := contextView middleButtonMenu.
    m notNil ifTrue:[
	m disable:#showMore.
    ].

    aContext isNil ifTrue:[
	text := Array with:'** no context **'.
	contextArray := nil.
    ] ifFalse:[
	text := OrderedCollection new:nChainShown.
	contextArray := OrderedCollection new:nChainShown.
	con := aContext.

	"
	 get them all
	"
	count := 0.
	[con notNil and:[count <= nChainShown]] whileTrue:[
	    contextArray add:con. count := count + 1.
	    (MoreDebuggingDetail == true) ifTrue:[
		text add:(((ObjectMemory addressOf:con) printStringRadix:16) , ' ' , con printString).
	    ] ifFalse:[
		text add:con printString.
	    ].

	    method := con method.
	    (method notNil and:[method isWrapped]) ifTrue:[
		"
		 kludge: if its a wrapped method, then hide the wrap-call
		"
		caller := con sender.
		(caller notNil and:[caller receiver == method originalMethod]) ifTrue:[
		    caller2 := caller sender.
		    (caller2 notNil and:[caller2 method == method]) ifTrue:[
			con := caller2
		    ]
		].
		caller := caller2 := nil
	    ].
	    con := con sender
	].

	"
	 did we reach the end ?
	"
	(con isNil or:[con sender isNil]) ifTrue:[
	    "
	     the very last one is the startup context
	     (in main) - it has nil as receiver and nil as selector
	    "
	    contextArray last selector isNil ifTrue:[
		contextArray removeLast.
		text removeLast
	    ]
	] ifFalse:[
	    m notNil ifTrue:[
		m enable:#showMore.
		text add:(resources string:'*** more walkback follows - click here to see them ***')
	    ].
	].
    ].

    contextView setList:text.
    releaseInspectors ifTrue:[
	receiverInspector release.
	contextInspector release.
    ].

    m notNil ifTrue:[
	m disable:#removeBreakpoint.
	m disable:#implementors.
	m disable:#senders.
	m disable:#browseClass.
    ].
    ^ true

    "Created: 14.12.1995 / 19:10:31 / cg"
!

showError:message
    codeView contents:(resources string:message).
    shown ifTrue:[
	exclusive ifTrue:[
	    "/ consider this a kludge:
	    "/ if exclusive, cannot use flash, since it suspends
	    "/ (but we cannot suspend here ...)
	    codeView redrawInverted. device flush.
	    OperatingSystem millisecondDelay:200.
	    codeView redraw
	] ifFalse:[
	    codeView flash
	]
    ]

    "Modified: 24.11.1995 / 22:07:30 / cg"
!

showTerminated
    self showError:'** the process has terminated **'
!

stepping 
    ^ stepping 
!

unstep 
    stepping := false.
    bigStep := false.
    steppedContextAddress := nil.
    exitAction := nil
!

updateContext
    |oldContext idx|

    inspectedProcess state == #dead ifTrue:[
	self showTerminated.
	^ self
    ].

    oldContext := selectedContext.
    (self setContext:(inspectedProcess suspendedContext)) ifTrue:[
	oldContext notNil ifTrue:[
	    contextArray notNil ifTrue:[
		idx := contextArray identityIndexOf:oldContext.
		idx ~~ 0 ifTrue:[
		    self showSelection:idx
		] ifFalse:[
		    codeView contents:('** context returned **')
		]
	    ]
	]
    ]
! !

!DebugView methodsFor:'private control loop'!

controlLoop
    "this is a kludge:
	start a dispatchloop which exits when
	either continue, return or step is pressed
    "

    haveControl := true.
    [haveControl] whileTrue:[
	self controlLoopCatchingErrors
    ].
    catchBlock := nil.
!

controlLoopCatchingErrors
    "this is the debuggers own private event handling loop;
     errors are cought, to prevent recursive debugger-invocations."

    "setup a self removing catch-block"
    catchBlock := [catchBlock := nil. ^ nil].

    (exclusive or:[windowGroup isNil]) ifTrue:[
        "if we do not have multiple processes or its a system process
         we start another dispatch loop, which exits when
         either continue, return or step is pressed
         or (via the catchBlock) if an error occurs.
         Since our display is an extra exclusive one, 
         all processing for normal views stops here ...
        "

        WindowGroup setActiveGroup:windowGroup.
        SignalSet anySignal handle:[:ex |
            |signal|

            signal := ex signal.
            self showError:'*** Error in modal debugger:

>>>> Signal:  ' , signal printString , '
>>>> In:      ' , ex suspendedContext printString , '
>>>> Message: ' , ex errorString , '

cought & ignored.'.
            ex return.
        ] do:[
            Object userNotificationSignal handle:[:ex |
                (ex signal == ActivityNotificationSignal) ifTrue:[
                    ex proceed
                ].
                self showError:ex errorString
            ] do:[
                device dispatchModalWhile:[Processor activeProcess state:#debug.
                                           haveControl].
            ]
        ].
        WindowGroup setActiveGroup:nil.
    ] ifFalse:[
        "we do have multiple processes -
         simply enter the DebugViews-Windowgroup event loop.
         effectively suspending event processing for the currently 
         active group.
        "
        SignalSet anySignal handle:[:ex |
            |answer signal|

            signal := ex signal.

            "/
            "/ ignore recursive breakpoints
            "/
            signal == MessageTracer breakpointSignal ifTrue:[
                'breakpoint in debugger ignored' errorPrintNL.
                ex proceed
            ].
            (signal == ActivityNotificationSignal) ifTrue:[
                ex proceed
            ].
            signal == Exception recursiveExceptionSignal ifTrue:[
                ex parameter signal == MessageTracer breakpointSignal ifTrue:[
                    'recursive breakpoint in debugger ignored' errorPrintNL.
                    ex proceed.
                ].

                self showError:'*** Recursive error in debugger:

>>>> Signal:  ' , ex signal printString , '
>>>>          ' , ex parameter signal printString , '
>>>> In:      ' , ex suspendedContext printString , '
>>>> Message: ' , ex errorString , '

cought & ignored.'.
                ex return
            ].

            self topView raiseDeiconified.    

            answer := Dialog 
                        choose:('error in debugger: ' , ex errorString , '\\debug again ?') withCRs
                        labels:#('debug' 'proceed' 'cancel' ) 
                        values:#(#debug #proceed #cancel) 
                        default:#cancel.
            answer == #debug ifTrue:[
                Debugger enterUnconditional:(ex suspendedContext) withMessage:'error in debugger: ' , ex errorString.
                ex proceed.
            ].
            answer == #proceed ifTrue:[
                ex proceed.
            ].
            ex return.
        ] do:[
            windowGroup eventLoopWhile:[Processor activeProcess state:#debug.
                                        true] onLeave:[]
        ].
    ].
    catchBlock := nil.

    "Created: 24.11.1995 / 20:33:45 / cg"
    "Modified: 7.5.1996 / 10:04:41 / cg"
! !

!DebugView methodsFor:'user interaction'!

codeAccept:someCode
    "user wants some code to be recompiled - must unwind stack since everything above
     and including selected method cannot be continued."

    "
     actually, this is not true, since the active methods will still be
     executed correctly - however, the code shown in the debugger is no
     longer in sync (showing the new code) with the executed code.
     Therefore, we hide those contexts to avoid confusion ....
     If you dont like this behavior, remove the 'inspecting ifFalse:' check below"

    "walk up context chain and find highest context which is either the selected context,
     or - if its a block-context - whose home is the selected context"

    |con top sel implementorClass method newMethod|

    codeView cursor:Cursor execute.

    "
     find the method-home context for this one
    "
    con := selectedContext.
    top := con.
    [con notNil] whileTrue:[
	(con methodHome == selectedContext) ifTrue:[
	    top := con
	].
	con := con sender
    ].
    "
     use class&selector to find the method for the compilation
     and compile.
    "
    sel := selectedContext selector.
    implementorClass := selectedContext methodClass.
    method := implementorClass compiledMethodAt:sel.
    newMethod := implementorClass compilerClass
			 compile:someCode
			 forClass:implementorClass
			 inCategory:(method category)
			 notifying:codeView.

    inspecting ifFalse:[
	"
	 if it worked, remove everything up to and including top
	 from context chain
	"
	(newMethod notNil and:[newMethod ~~ #Error]) ifTrue:[
	    self setContext:(top sender).

	    "
	     continue/step is no longer possible
	    "
	    canContinue := false.
	    self showSelection:1.
	    exitAction := #return
	].
    ].
    codeView cursor:Cursor normal
!

destroy
    "closing the debugger implies an abort or continue"

    contextView middleButtonMenu hide.

    inspecting ifFalse:[
        CachedExclusive == self ifTrue:[
            CachedExclusive := nil.
        ].
        CachedDebugger == self ifTrue:[
            CachedDebugger := nil
        ].

        inspecting ifFalse:[
            canAbort ifTrue:[
                self doAbort.
            ] ifFalse:[
                self doContinue
            ]
        ].
        'DEBUGGER: OOPS - non regular debugView closing' infoPrintCR.
        DebugView newDebugger.
    ].

    "
     we manually release all private data, since the Debugger
     is cached for reuse - thus the memory would not be collectable
     otherwise.
    "
    codeView acceptAction:nil.
    codeView doItAction:nil.
    codeView contents:nil.
    catchBlock := nil.

    receiverInspector release.
    contextInspector release.
    inspectedProcess := nil.
    exitAction := nil.
    contextArray := nil.
    selectedContext := actualContext := nil.
    grabber := nil.
    self autoUpdateOff.

    super destroy    "/ 1.12.94

    "Modified: 20.5.1996 / 10:31:55 / cg"
!

showSelection:lineNr
    "user clicked on a header line - show selected code in textView.
     Also sent to autoselect an interesting context on entry."

    |con homeContext sel method code canAccept
     implementorClass lineNrInMethod rec m line
     sender selSender tryVars possibleBlocks errMsg 
     mthd cls w|

    contextArray notNil ifTrue:[
        lineNr <= contextArray size ifTrue:[
            con := contextArray at:lineNr.
        ].
        "
         clicking on the '** ...'-line shows more ...
        "
        con isNil ifTrue:[
            line := contextView list at:lineNr.
            (line startsWith:'**') ifTrue:[
                self showMore.
                contextView setSelection:lineNr.
                con := contextArray at:lineNr
            ].
            con isNil ifTrue:[^ self].
        ].

        self withWaitCursorDo:[
            "
             give it to the (lower right) inspector
            "
            contextInspector inspect:con.

            "
             get the home context
            "
            con isBlockContext ifTrue:[
                homeContext := con methodHome
            ] ifFalse:[
                homeContext := con
            ].
            con canReturn ifTrue:[
                returnButton enable. restartButton enable.
            ] ifFalse:[
                returnButton disable. restartButton disable.
            ].

            lineNrInMethod := con lineNumber.

            canAccept := false.

            homeContext isNil ifTrue:[
                "
                 mhmh - an optimized block
                 should get the block here, and get the method from
                 that one ...
                 But in 2.10.x, there is no easy way to get to the block
                 since that one is not in the context.
                 Starting with 2.11, the new block calling scheme will fix this.
                "

                "temporary kludge - peek into the sender context.
                 If its a do-like method and there is a single block variable 
                 in the args or temporaries, that must be the one.
                 This helps in some cases.
                "
                (sender := con sender) notNil ifTrue:[
                    tryVars := false.
                    (selSender := sender selector) notNil ifTrue:[
                        (selSender endsWith:'do:') ifTrue:[
                            tryVars := true.
                        ] ifFalse:[
                            (selSender endsWith:'Do:') ifTrue:[
                                tryVars := true.
                            ]
                        ]
                    ].
                    tryVars ifTrue:[
                        possibleBlocks := sender argsAndVars select:[:v | v isBlock].
                        possibleBlocks := possibleBlocks select:[:b | b home isNil].
                        possibleBlocks size == 1 ifTrue:[
                            method := possibleBlocks first method.
                        ].
                    ]
                ].

            ] ifFalse:[
                "fetch rec here - so we wont need context in doItAction"
                rec := homeContext receiver.

                sel := homeContext selector.
                sel notNil ifTrue:[
                    canAccept := true.

                    implementorClass := homeContext methodClass.
                    implementorClass isNil ifTrue:[
                        "
                         special: look if this context was created by
                         valueWithReceiver kind of method invocation;
                         if so, grab the method from the sender and show it
                        "
                        ((sender := con sender) notNil
                        and:[(sender selector startsWith:'valueWithReceiver:')
                        and:[sender receiver isMethod]]) ifTrue:[
                            method := sender receiver.
                            code := method source.
                            canAccept := false.
                        ] ifFalse:[
                            (method := con method) notNil ifTrue:[
                                code := method source.
                                canAccept := false.
                            ]
                        ]
                    ] ifFalse:[
                        method := implementorClass compiledMethodAt:sel.
                    ].
                ]
            ].

            code isNil ifTrue:[
                errMsg := nil.
                method notNil ifTrue:[
                    code := method source.
                    code isNil ifTrue:[
                        method sourceFilename notNil ifTrue:[
                            codeView contents:(resources 
                                                       string:'** no sourcefile: %1 **'
                                                       with:method sourceFilename).
                            codeView flash
                        ] ifFalse:[
                            errMsg := '** no source **'
                        ]
                    ]
                ] ifFalse:[
                    homeContext isNil ifTrue:[
                        errMsg := '** sorry; cannot show code of all optimized blocks (yet) **'.
                    ] ifFalse:[
                        errMsg := '** no method - no source **'
                    ]
                ].
                errMsg notNil ifTrue:[
                   self showError:errMsg
                ]
            ].

            code isNil ifTrue:[
                canAccept := false.
            ] ifFalse:[
                codeView contents:code.
                (lineNrInMethod notNil and:[lineNrInMethod ~~ 0]) ifTrue:[
"/                    lineNrInMethod > codeView list size ifTrue:[
"/                        lineNrInMethod := codeView list size + 1
"/                    ].
"/                    codeView selectLine:lineNrInMethod.
"/                    codeView makeSelectionVisible

                    lineNrInMethod <= codeView list size ifTrue:[
                        (lineNrInMethod == 255 
                        and:[method notNil
                        and:[method code isNil]]) ifTrue:[
                            "/ means: do not really know in interpreted methods
                            codeView selectFromLine:255 col:1 toLine:codeView list size + 1 col:0.
                        ] ifFalse:[
                            codeView selectLine:lineNrInMethod.
                        ].
                        codeView makeSelectionVisible
                    ]
                ].
            ].

            canAccept ifTrue:[
                codeView acceptAction:[:code | self codeAccept:code asString]
            ] ifFalse:[
                codeView acceptAction:nil.
            ].

            receiverInspector inspect:rec.

            "
             the one below is wrong: currently, the
             evaluator cannot handle passed contexts.
             Once it does, pass con as in:-arg
            "
            codeView doItAction:[:theCode |
                             rec class evaluatorClass 
                                 evaluate:theCode 
                                 in:nil            "/ *** con
                                 receiver:rec 
                                 notifying:codeView 
                                 logged:true 
                                 ifFail:nil 
            ].

            selectedContext := homeContext.
            actualContext := con
        ].
    ].

    "clear out locals to prevent keeping around unneeded contexts 
     (due to the block held in codeView).
     (not really needed, since stuff gets collected away sooner or later ...
      ... but this makes it a bit sooner)
    "
    con := nil.
    homeContext := nil.

    "
     enable/disable some menu items
    "
    m := contextView middleButtonMenu.
    (m notNil and:[selectedContext notNil]) ifTrue:[
        m enableAll:#(implementors senders inspectContext skip skipForReturn).

        (method notNil and:[method isWrapped]) ifTrue:[
            m enable:#removeBreakpoint.
        ] ifFalse:[
            m disable:#removeBreakpoint.
        ].

        mthd := selectedContext method.
        mthd notNil ifTrue:[
            w := mthd who.
        ].
        m enable:#browseClass.
        w notNil ifTrue:[
            cls := w at:1
        ].
        cls notNil ifTrue:[
            m enableAll:#(browse browseClass browseClassHierarchy browseFullClassProtocol).
        ] ifFalse:[
            m disableAll:#(browse browseClass browseClassHierarchy browseFullClassProtocol).
        ].
    ]

    "Modified: 25.5.1996 / 12:26:58 / cg"
! !

!DebugView class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libtool/DebugView.st,v 1.86 1996-05-29 11:23:56 cg Exp $'
! !