more skipping in dense backtrace
authorClaus Gittinger <cg@exept.de>
Mon, 05 Jan 1998 14:05:15 +0100
changeset 1386 55632b45ced2
parent 1385 4bca25dd2143
child 1387 355fc1057e11
more skipping in dense backtrace
DebugView.st
--- a/DebugView.st	Fri Dec 19 15:07:39 1997 +0100
+++ b/DebugView.st	Mon Jan 05 14:05:15 1998 +0100
@@ -67,17 +67,17 @@
     a halfway destroyed 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
+	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
+	Claus Gittinger
 
     [see also:]
-        Exception Signal
-        Process
+	Exception Signal
+	Process
 "
 ! !
 
@@ -121,25 +121,25 @@
     StepInterruptPending := nil.
 
     thisContext isRecursive ifTrue:[
-        "/ care for the special case, were the Debugger was autoloaded.
-        "/ in this case, thisContext IS recursive, but thats no error
-        "/ condition.
-        found := false.
-        c := thisContext sender.
-        [found not
-         and:[c notNil 
-         and:[c selector ~~ #enter:withMessage:]]] whileTrue:[
-            c selector == #noByteCode ifTrue:[
-                found := true
-            ].
-            c := c sender
-        ].
-
-        found ifFalse:[
-            ('DebugView [warning]: reentered with: ', aString) errorPrintCR.
-            ^ MiniDebugger 
-                enterWithMessage:'DebugView [error]: recursive error (in debugger)'.
-        ]
+	"/ care for the special case, were the Debugger was autoloaded.
+	"/ in this case, thisContext IS recursive, but thats no error
+	"/ condition.
+	found := false.
+	c := thisContext sender.
+	[found not
+	 and:[c notNil 
+	 and:[c selector ~~ #enter:withMessage:]]] whileTrue:[
+	    c selector == #noByteCode ifTrue:[
+		found := true
+	    ].
+	    c := c sender
+	].
+
+	found ifFalse:[
+	    ('DebugView [warning]: reentered with: ', aString) errorPrintCR.
+	    ^ MiniDebugger 
+		enterWithMessage:'DebugView [error]: recursive error (in debugger)'.
+	]
     ].
 
     "
@@ -149,17 +149,17 @@
      stepping debugger to come up again instead of a new one.
     "
     OpenDebuggers notNil ifTrue:[
-        active := Processor activeProcess.
-        OpenDebuggers do:[:aDebugger |
-            (aDebugger notNil and:[aDebugger ~~ 0]) ifTrue:[
-                (aDebugger inspectedProcess == active) ifTrue:[
+	active := Processor activeProcess.
+	OpenDebuggers do:[:aDebugger |
+	    (aDebugger notNil and:[aDebugger ~~ 0]) ifTrue:[
+		(aDebugger inspectedProcess == active) ifTrue:[
 "/ 'entering stepping debugger again' printNL.
-                    aDebugger unstep.
-                    aDebugger setLabelFor:aString in:active.
-                    ^ aDebugger enter:aContext select:nil.
-                ]
-            ]
-        ]
+		    aDebugger unstep.
+		    aDebugger setLabelFor:aString in:active.
+		    ^ aDebugger enter:aContext select:nil.
+		]
+	    ]
+	]
     ].
 
     ^ self enterUnconditional:aContext withMessage:aString
@@ -176,21 +176,21 @@
     proc := Processor activeProcess.
 
     (MessageTracer notNil and:[MessageTracer isLoaded]) ifTrue:[
-        breakpointSignal := MessageTracer breakpointSignal.
+	breakpointSignal := MessageTracer breakpointSignal.
     ].
     breakpointSignal notNil ifTrue:[
-        breakpointSignal handle:[:ex |
-            'DebugView [info]: breakpoint in debugger ignored' infoPrintCR.
-            ex proceed
-        ] do:[
-            aDebugger := self new.
-            aDebugger setLabelFor:aString in:proc.
-            aDebugger enter:aContext select:nil.
-        ]
+	breakpointSignal handle:[:ex |
+	    'DebugView [info]: breakpoint in debugger ignored' infoPrintCR.
+	    ex proceed
+	] do:[
+	    aDebugger := self new.
+	    aDebugger setLabelFor:aString in:proc.
+	    aDebugger enter:aContext select:nil.
+	]
     ] ifFalse:[
-        aDebugger := self new.
-        aDebugger setLabelFor:aString in:proc.
-        aDebugger enter:aContext select:nil.
+	aDebugger := self new.
+	aDebugger setLabelFor:aString in:proc.
+	aDebugger enter:aContext select:nil.
     ].
     ^ nil
 
@@ -220,37 +220,37 @@
      (because otherwise we would not get any events here ...
     "
     Processor activeProcessIsSystemProcess ifTrue:[
-        (CachedExclusive isNil 
-        or:[CachedExclusive device ~~ Screen current]) ifTrue:[
-            debugger := self newExclusive
-        ] ifFalse:[
-            debugger := CachedExclusive.
-            CachedExclusive := nil.
-        ].
+	(CachedExclusive isNil 
+	or:[CachedExclusive device ~~ Screen current]) ifTrue:[
+	    debugger := self newExclusive
+	] ifFalse:[
+	    debugger := CachedExclusive.
+	    CachedExclusive := nil.
+	].
     ] ifFalse:[
-        CachedDebugger notNil ifTrue:[
-            (CachedDebugger device ~~ Screen current 
-            or:[CachedDebugger device isOpen not]) ifTrue:[
-                CachedDebugger := nil
-            ]
-        ].
-
-        CachedDebugger isNil ifTrue:[
-            Screen current isOpen ifFalse:[
-                DeviceWorkstation currentScreenQuerySignal handle:[:ex |
-                    ex proceedWith:Display
-                ] do:[
-                    debugger := super new.
-                ]
-            ] ifTrue:[
-                debugger := super new.
-            ].
-            debugger label:'Debugger'.
-            debugger icon:self defaultIcon.
-        ] ifFalse:[
-            debugger := CachedDebugger.
-            CachedDebugger := nil.
-        ]
+	CachedDebugger notNil ifTrue:[
+	    (CachedDebugger device ~~ Screen current 
+	    or:[CachedDebugger device isOpen not]) ifTrue:[
+		CachedDebugger := nil
+	    ]
+	].
+
+	CachedDebugger isNil ifTrue:[
+	    Screen current isOpen ifFalse:[
+		DeviceWorkstation currentScreenQuerySignal handle:[:ex |
+		    ex proceedWith:Display
+		] do:[
+		    debugger := super new.
+		]
+	    ] ifTrue:[
+		debugger := super new.
+	    ].
+	    debugger label:'Debugger'.
+	    debugger icon:self defaultIcon.
+	] ifFalse:[
+	    debugger := CachedDebugger.
+	    CachedDebugger := nil.
+	]
     ].
     ^ debugger
 
@@ -280,15 +280,15 @@
     aDebugger := super new.
     aDebugger icon:self defaultIcon.
     aProcess notNil ifTrue:[
-        nm := aProcess name.
-        nm notNil ifTrue:[
-            nm := (nm contractTo:17) , '-' , aProcess id printString
-        ] ifFalse:[
-            nm := aProcess id printString
-        ].
-        label := 'Debugger [' , nm , ']'.
+	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'
+	label := 'no process'
     ].
     aDebugger label:label iconLabel:'Debugger'.
     aDebugger openOn:aProcess.
@@ -335,20 +335,20 @@
     |nm i|
 
     (i := DefaultIcon) isNil ifTrue:[
-        i := self classResources at:'ICON' default:nil.
-        i isNil ifTrue:[
-            nm := ClassResources at:'ICON_FILE' default:'Debugger.xbm'.
-            i := Image fromFile:nm resolution:100.
-            i isNil ifTrue:[
-                i := Image fromFile:('bitmaps/' , nm) resolution:100.
-                i isNil ifTrue:[
-                    i := StandardSystemView defaultIcon
-                ]
-            ]
-        ].
-        i notNil ifTrue:[
-            DefaultIcon := i := i on:Display
-        ]
+	i := self classResources at:'ICON' default:nil.
+	i isNil ifTrue:[
+	    nm := ClassResources at:'ICON_FILE' default:'Debugger.xbm'.
+	    i := Image fromFile:nm resolution:100.
+	    i isNil ifTrue:[
+		i := Image fromFile:('bitmaps/' , nm) resolution:100.
+		i isNil ifTrue:[
+		    i := StandardSystemView defaultIcon
+		]
+	    ]
+	].
+	i notNil ifTrue:[
+	    DefaultIcon := i := i on:Display
+	]
     ].
     ^ i
 
@@ -383,11 +383,11 @@
     delta := self interestingContextIndexFrom:aContext.
     con := aContext.
     [con notNil and:[delta > 1]] whileTrue:[
-        con := con sender.
-        delta := delta - 1.
+	con := con sender.
+	delta := delta - 1.
     ].
     con isNil ifTrue:[
-        ^ aContext
+	^ aContext
     ].
     ^ con
 
@@ -413,22 +413,22 @@
 
     c := aContext.
     1 to:5 do:[:i |
-        c isNil ifTrue:[^ 1].
-        sel := c selector.
-        ((sel == #raise) 
-        or:[sel == #raiseRequest]) ifTrue:[
-            (c receiver isKindOf:Exception) ifTrue:[
-                ex := c receiver.
-                offset := i.
-                found := c
-            ] ifFalse:[
-                (c receiver isSignal) ifTrue:[
-                    offset := i.
-                    found := c
-                ]
-            ]
-        ].
-        c := c sender.
+	c isNil ifTrue:[^ 1].
+	sel := c selector.
+	((sel == #raise) 
+	or:[sel == #raiseRequest]) ifTrue:[
+	    (c receiver isKindOf:Exception) ifTrue:[
+		ex := c receiver.
+		offset := i.
+		found := c
+	    ] ifFalse:[
+		(c receiver isSignal) ifTrue:[
+		    offset := i.
+		    found := c
+		]
+	    ]
+	].
+	c := c sender.
     ].
 
     "
@@ -436,24 +436,24 @@
      to the erronous context
     "
     ex notNil ifTrue:[
-        ex signal == Signal noHandlerSignal ifTrue:[
-            c := ex suspendedContext
-        ]
+	ex signal == Signal noHandlerSignal ifTrue:[
+	    c := ex suspendedContext
+	]
     ].
 
     (c := found) isNil ifTrue:[
-        "/ this is a kludge, but convenient.
-        "/ show the place where the divisionByZero happend,
-        "/ not where the signal was raised.
-
-        sel := aContext selector.
-        (sel == #//      
-        or:[sel == #/
-        or:[sel == #\\]]) ifTrue:[
-            ^ 2
-        ].
-
-        ^ 1
+	"/ this is a kludge, but convenient.
+	"/ show the place where the divisionByZero happend,
+	"/ not where the signal was raised.
+
+	sel := aContext selector.
+	(sel == #//      
+	or:[sel == #/
+	or:[sel == #\\]]) ifTrue:[
+	    ^ 2
+	].
+
+	^ 1
     ].
 
     "
@@ -462,12 +462,12 @@
     "
     prev := nil.
     [   
-        ((c receiver isSignal)
-        or:[(c receiver isKindOf:Exception)])
+	((c receiver isSignal)
+	or:[(c receiver isKindOf:Exception)])
     ] whileTrue:[
-        prev := c.
-        (c := c sender) isNil ifTrue:[^ offset].
-        offset := offset + 1.
+	prev := c.
+	(c := c sender) isNil ifTrue:[^ offset].
+	offset := offset + 1.
     ].
 
     "
@@ -478,29 +478,29 @@
      if the sender-method of the raise is one of objects error methods ...
     "
     ( #( halt halt: 
-         error error: 
-         doesNotUnderstand: 
-         subclassResponsibility 
-         primitiveFailed) includes:c selector) 
+	 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.
+	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
+	"
+	 ok, got the raise - if its a BreakPoint, look for the sender
+	"
+	(MessageTracer notNil
 	 and:[MessageTracer isLoaded
 	 and:[prev receiver == MessageTracer breakpointSignal]]) ifTrue:[
-            offset := offset + 1
-        ].
+	    offset := offset + 1
+	].
     ].
 
     ^ offset
@@ -521,10 +521,10 @@
     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"
+	(where receiver == DebugView) ifTrue:[
+	    where := where sender
+	]
+	"where is now interrupted methods context"
     ].
     ^ self enter:where select:nil
 
@@ -559,56 +559,56 @@
     "/ on a multiUser system, better ungrab all of them ...
 
     Screen allScreens do:[:aScreen |
-        aScreen ungrabPointer.
-        aScreen ungrabKeyboard.
+	aScreen ungrabPointer.
+	aScreen ungrabKeyboard.
     ].
 
     ("inspectedProcess suspendedContext isNil 
     or:["inspectedProcess isSystemProcess"]") ifTrue:[
 
-        terminateButton disable.
+	terminateButton disable.
     ] ifFalse:[
-        terminateButton enable.
-        abortButton enable.
+	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 skipForReturn inspectContext).
-        ].
-        verboseBacktrace 
-            ifTrue:[self showVerboseBacktrace]
-            ifFalse:[self showDenseBacktrace].
+	"
+	 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 skipForReturn inspectContext).
+	].
+	verboseBacktrace 
+	    ifTrue:[self showVerboseBacktrace]
+	    ifFalse:[self showDenseBacktrace].
     ] ifFalse:[
-        self iconLabel:'Debugger'.
+	self iconLabel:'Debugger'.
     ].
 
     windowGroup isNil ifTrue:[
-        windowGroup := WindowGroup new.
-        windowGroup addTopView:self.
+	windowGroup := WindowGroup new.
+	windowGroup addTopView:self.
     ].
     exclusive ifFalse:[
-        "/ create a (modal) windowGroup for myself
-
-        windowGroup setModal:true.
+	"/ create a (modal) windowGroup for myself
+
+	windowGroup setModal:true.
     ] ifTrue:[
-        "/ create a windowGroup with a synchronous sensor for me
-
-        windowGroup sensor:(SynchronousWindowSensor new).
+	"/ create a windowGroup with a synchronous sensor for me
+
+	windowGroup sensor:(SynchronousWindowSensor new).
     ].
     windowGroup setProcess:Processor activeProcess.
 
@@ -619,95 +619,95 @@
 
 
     initialSelectionOrNil notNil ifTrue:[
-        selection := initialSelectionOrNil
+	selection := initialSelectionOrNil
     ] ifFalse:[
-        "
-         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.
-        "
-        con1 := (contextArray at:1 ifAbsent:nil).
-        con2 := (contextArray at:2 ifAbsent:nil).
-        exitAction == #step ifTrue:[
-
-            selection := 1.
-            steppedContext notNil ifTrue:[
+	"
+	 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.
+	"
+	con1 := (contextArray at:1 ifAbsent:nil).
+	con2 := (contextArray at:2 ifAbsent:nil).
+	exitAction == #step ifTrue:[
+
+	    selection := 1.
+	    steppedContext notNil ifTrue:[
             
-                "
-                 if we came here by a big-step, show the method where we are
-                "
-                con1 == steppedContext ifTrue:[
-                    selection := 1
-                ] ifFalse:[
-                    con2 == steppedContext ifTrue:[
-                        selection := 2
-                    ]
-                ].
-                "
-                 for bigStep, we could also be in a block below the actual method ...
-                "
-                (con1 home notNil 
-                 and:[con1 home == steppedContext]) ifTrue:[
-                    selection := 1
-                ] ifFalse:[
-                    (con2 home notNil 
-                    and:[con2 home == steppedContext]) ifTrue:[
-                        selection := 2
-                    ]
-                ].
-            ]
-        ] ifFalse:[
-            steppedContext isNil ifTrue:[
-                "
-                 preselect a more interesting context, (where halt/raise was ...)
-                "
-                selection := self class interestingContextIndexFrom:aContext.
-            ] ifFalse:[
-                "
-                 if we came here by a big-step, show the method where we are
-                "
-                con1 == steppedContext ifTrue:[
-                    selection := 1
-                ] ifFalse:[
-                    con2 == steppedContext ifTrue:[
-                        selection := 2
-                    ]
-                ]
-            ]
-        ].
-
-        con1 := nil.
-        con2 := nil.
+		"
+		 if we came here by a big-step, show the method where we are
+		"
+		con1 == steppedContext ifTrue:[
+		    selection := 1
+		] ifFalse:[
+		    con2 == steppedContext ifTrue:[
+			selection := 2
+		    ]
+		].
+		"
+		 for bigStep, we could also be in a block below the actual method ...
+		"
+		(con1 home notNil 
+		 and:[con1 home == steppedContext]) ifTrue:[
+		    selection := 1
+		] ifFalse:[
+		    (con2 home notNil 
+		    and:[con2 home == steppedContext]) ifTrue:[
+			selection := 2
+		    ]
+		].
+	    ]
+	] ifFalse:[
+	    steppedContext isNil ifTrue:[
+		"
+		 preselect a more interesting context, (where halt/raise was ...)
+		"
+		selection := self class interestingContextIndexFrom:aContext.
+	    ] ifFalse:[
+		"
+		 if we came here by a big-step, show the method where we are
+		"
+		con1 == steppedContext ifTrue:[
+		    selection := 1
+		] ifFalse:[
+		    con2 == steppedContext ifTrue:[
+			selection := 2
+		    ]
+		]
+	    ]
+	].
+
+	con1 := nil.
+	con2 := nil.
     ].
 
     selection notNil ifTrue:[
-        self showSelection:selection.
-        contextView setSelection:selection.
-        selection > 1 ifTrue:[
-            contextView scrollToLine:(selection - 1)
-        ]
+	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.
-        ]
+	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.
+	]
     ].
 
     "
@@ -717,14 +717,14 @@
      position again
     "
     drawableId notNil ifTrue:[
-        self remap.
+	self remap.
     ] ifFalse:[
-        self realize.
+	self realize.
     ].
     self realizeAllSubViews.
 
     exclusive ifTrue:[
-        self showError:'
+	self showError:'
 Debugging system process `' , (inspectedProcess nameOrId) printString , '''.
 
 This is a modal debugger - all event processing is stopped..
@@ -751,10 +751,10 @@
     "
 
     [self controlLoop] valueOnUnwindDo:[
-        windowGroup notNil ifTrue:[
-            windowGroup setProcess:nil.
-        ].
-        self destroy
+	windowGroup notNil ifTrue:[
+	    windowGroup setProcess:nil.
+	].
+	self destroy
     ].
 
     "
@@ -770,35 +770,35 @@
     "/ codeView 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 |
-                'DebugView [info]: ignored error while unwinding: ' infoPrint.
-                ex errorString infoPrintCR.
-
-                ex proceed
-            ] do:[
-                Object abortSignal raise.
-            ].
-            'DebugView [warning]: abort failed' errorPrintCR
-        ].
-
-        (exitAction == #return) ifTrue:[
-            selectedContext notNil ifTrue:[
-                "
-                 if there is a selection in the codeView,
-                 evaluate it and use the result as return value
-                "
+	receiverInspector release.
+	contextInspector release.
+
+	self unmap.
+	device flush.
+
+	(exitAction == #abort) ifTrue:[
+	    self cacheMyself.
+
+	    "
+	     have to catch errors occuring in unwind-blocks
+	    "
+	    ErrorSignal handle:[:ex |
+		'DebugView [info]: ignored error while unwinding: ' infoPrint.
+		ex errorString infoPrintCR.
+
+		ex proceed
+	    ] do:[
+		Object abortSignal raise.
+	    ].
+	    'DebugView [warning]: abort failed' errorPrintCR
+	].
+
+	(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
@@ -816,160 +816,160 @@
 "/                    ].
 "/                ].
 
-                con := selectedContext.
-                self cacheMyself.
-                "
-                 have to catch errors occuring in unwind-blocks
-                "
-                Object errorSignal handle:[:ex |
-                    'DebugView [info]: ignored error while unwinding: ' errorPrint.
-                    ex errorString errorPrintCR.
-                    ex proceed
-                ] do:[
-                    con unwind:retval.
-                ].
-                'DebugView [warning]: cannot return from selected context' errorPrintCR
-            ]
-        ].
-
-        (exitAction == #restart) ifTrue:[
-            selectedContext notNil ifTrue:[
-                con := selectedContext.
-                self cacheMyself.
-                "
-                 have to catch errors occuring in unwind-blocks
-                "
-                Object errorSignal handle:[:ex |
-                    'DebugView [info]: ignored error while unwinding: ' infoPrint.
-                    ex errorString infoPrintCR.
-                    ex proceed
-                ] do:[
-                    con unwindAndRestart.
-                ].
-                'DebugView [warning]: cannot restart selected context' errorPrintCR
-            ]
-        ].
-
-        (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 |
-                'DebugView [info]: ignored error while unwinding: ' infoPrint.
-                ex errorString infoPrintCR.
-                ex proceed
-            ] do:[
-                Processor activeProcess terminate.
-            ].
-            'DebugView [warning]: cannot terminate process' errorPrintCR
-        ]
+		con := selectedContext.
+		self cacheMyself.
+		"
+		 have to catch errors occuring in unwind-blocks
+		"
+		Object errorSignal handle:[:ex |
+		    'DebugView [info]: ignored error while unwinding: ' errorPrint.
+		    ex errorString errorPrintCR.
+		    ex proceed
+		] do:[
+		    con unwind:retval.
+		].
+		'DebugView [warning]: cannot return from selected context' errorPrintCR
+	    ]
+	].
+
+	(exitAction == #restart) ifTrue:[
+	    selectedContext notNil ifTrue:[
+		con := selectedContext.
+		self cacheMyself.
+		"
+		 have to catch errors occuring in unwind-blocks
+		"
+		Object errorSignal handle:[:ex |
+		    'DebugView [info]: ignored error while unwinding: ' infoPrint.
+		    ex errorString infoPrintCR.
+		    ex proceed
+		] do:[
+		    con unwindAndRestart.
+		].
+		'DebugView [warning]: cannot restart selected context' errorPrintCR
+	    ]
+	].
+
+	(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 |
+		'DebugView [info]: ignored error while unwinding: ' infoPrint.
+		ex errorString infoPrintCR.
+		ex proceed
+	    ] do:[
+		Processor activeProcess terminate.
+	    ].
+	    'DebugView [warning]: cannot terminate process' errorPrintCR
+	]
     ].
 
     selectedContext := actualContext := firstContext := nil.
 
     grabber notNil ifTrue:[
-        device grabPointerInView:grabber.
-        grabber := nil.
+	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
-        "
-
-        "/
-        "/ also must care for stepping into a return
-        "/
-        steppedContext notNil ifTrue:[
-            Processor activeProcess forceInterruptOnReturnOf:steppedContext.
-        ].
-
-        OpenDebuggers isNil ifTrue:[
-            OpenDebuggers := WeakArray with:self
-        ] ifFalse:[
-            (OpenDebuggers includes:self) ifFalse:[
-                idx := OpenDebuggers identityIndexOf:nil.
-                idx == 0 ifTrue:[
-                    idx := OpenDebuggers identityIndexOf:0
-                ].
-                idx ~~ 0 ifTrue:[
-                    OpenDebuggers at:idx put:self
-                ] ifFalse:[
-                    OpenDebuggers := OpenDebuggers copyWith:self
-                ]
-            ]
-        ].
-        self label:'single stepping - please wait ...'.
-        stepping := true.
-
-        ObjectMemory stepInterruptHandler:self.
-        Context singleStepInterruptRequest isHandled ifTrue:[
-            "bigStep" steppedContextLineno notNil ifTrue:[   
-                Context singleStepInterruptRequest raiseWith:#next
-            ] ifFalse:[
-                Context singleStepInterruptRequest raiseWith:#step
-            ]
-        ] ifFalse:[
-            "/ see if we came here through an interrupt-action
-            "/ (i.e. aProcess interruptWith:...)
+	"
+	 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
+	"
+
+	"/
+	"/ also must care for stepping into a return
+	"/
+	steppedContext notNil ifTrue:[
+	    Processor activeProcess forceInterruptOnReturnOf:steppedContext.
+	].
+
+	OpenDebuggers isNil ifTrue:[
+	    OpenDebuggers := WeakArray with:self
+	] ifFalse:[
+	    (OpenDebuggers includes:self) ifFalse:[
+		idx := OpenDebuggers identityIndexOf:nil.
+		idx == 0 ifTrue:[
+		    idx := OpenDebuggers identityIndexOf:0
+		].
+		idx ~~ 0 ifTrue:[
+		    OpenDebuggers at:idx put:self
+		] ifFalse:[
+		    OpenDebuggers := OpenDebuggers copyWith:self
+		]
+	    ]
+	].
+	self label:'single stepping - please wait ...'.
+	stepping := true.
+
+	ObjectMemory stepInterruptHandler:self.
+	Context singleStepInterruptRequest isHandled ifTrue:[
+	    "bigStep" steppedContextLineno notNil ifTrue:[   
+		Context singleStepInterruptRequest raiseWith:#next
+	    ] ifFalse:[
+		Context singleStepInterruptRequest raiseWith:#step
+	    ]
+	] ifFalse:[
+	    "/ see if we came here through an interrupt-action
+	    "/ (i.e. aProcess interruptWith:...)
         
-            enteredByInterrupt := false.
-            con := thisContext findNextContextWithSelector:#timerInterrupt or:#ioInterrupt or:nil.
-            [enteredByInterrupt not
-             and:[con notNil 
-             and:[con ~~ aContext]]] whileTrue:[
-                ((sel := con selector) == #timerInterrupt
-                or:[sel == #ioInterrupt]) ifTrue:[
-                    enteredByInterrupt := true.
-                ] ifFalse:[
-                    con := con findNextContextWithSelector:#timerInterrupt or:#ioInterrupt or:nil.
-                ].
-            ].
-
-            ObjectMemory flushInlineCaches.
-
-            enteredByInterrupt ifTrue:[
-                "/ dont want to step through all intermediate
-                "/ (scheduler-) contexts; place a return-trap on the
-                "/ one right below the interesting one
+	    enteredByInterrupt := false.
+	    con := thisContext findNextContextWithSelector:#timerInterrupt or:#ioInterrupt or:nil.
+	    [enteredByInterrupt not
+	     and:[con notNil 
+	     and:[con ~~ aContext]]] whileTrue:[
+		((sel := con selector) == #timerInterrupt
+		or:[sel == #ioInterrupt]) ifTrue:[
+		    enteredByInterrupt := true.
+		] ifFalse:[
+		    con := con findNextContextWithSelector:#timerInterrupt or:#ioInterrupt or:nil.
+		].
+	    ].
+
+	    ObjectMemory flushInlineCaches.
+
+	    enteredByInterrupt ifTrue:[
+		"/ dont want to step through all intermediate
+		"/ (scheduler-) contexts; place a return-trap on the
+		"/ one right below the interesting one
 
 "/                'special unwind return' printCR.
-                con unwindThenDo:[
-                                  ObjectMemory stepInterruptHandler:self.
-                                  InStepInterrupt := nil.
-                                  StepInterruptPending := 1.
-                                  InterruptPending := 1].
-            ] ifFalse:[
+		con unwindThenDo:[
+				  ObjectMemory stepInterruptHandler:self.
+				  InStepInterrupt := nil.
+				  StepInterruptPending := 1.
+				  InterruptPending := 1].
+	    ] ifFalse:[
 "/                'normal step return' printCR.
-                skipLineNr ~~ #return ifTrue:[
-                    StepInterruptPending := 1.
-                    InterruptPending := 1.
-                ] ifFalse:[
+		skipLineNr ~~ #return ifTrue:[
+		    StepInterruptPending := 1.
+		    InterruptPending := 1.
+		] ifFalse:[
 "/                    'step for return' printCR.
-                ]
-            ].
-            InStepInterrupt := nil
-        ]
+		]
+	    ].
+	    InStepInterrupt := nil
+	]
     ] ifFalse:[
-        OpenDebuggers notNil ifTrue:[
-            idx := OpenDebuggers identityIndexOf:self.
-            idx ~~ 0 ifTrue:[
-                OpenDebuggers at:idx put:nil
-            ]
-        ].
-        self cacheMyself.
+	OpenDebuggers notNil ifTrue:[
+	    idx := OpenDebuggers identityIndexOf:self.
+	    idx ~~ 0 ifTrue:[
+		OpenDebuggers at:idx put:nil
+	    ]
+	].
+	self cacheMyself.
     ]
 
     "Modified: / 17.4.1997 / 13:01:32 / stefan"
@@ -1005,21 +1005,21 @@
     bpanel elementsChangeSize:true.
 
     aProcess state == #run ifTrue:[
-        device hasColors ifTrue:[
-            continueButton foregroundColor:Color red darkened.
-        ].
-        continueButton label:(resources at:'stop').
-        continueButton action:[self doStop].
-        returnButton disable.
-        restartButton disable.
+	device hasColors ifTrue:[
+	    continueButton foregroundColor:Color red darkened.
+	].
+	continueButton label:(resources at:'stop').
+	continueButton action:[self doStop].
+	returnButton disable.
+	restartButton disable.
     ] ifFalse:[
-        device hasColors ifTrue:[
-            continueButton foregroundColor:Color green darkened darkened.
-        ].
-        continueButton label:(resources at:'continue').
-        continueButton action:[self doContinue].
-        returnButton enable.
-        restartButton enable.
+	device hasColors ifTrue:[
+	    continueButton foregroundColor:Color green darkened darkened.
+	].
+	continueButton label:(resources at:'continue').
+	continueButton action:[self doContinue].
+	returnButton enable.
+	restartButton enable.
     ].
 
     dummy := View extent:(10 @ 5) in:bpanel.
@@ -1029,9 +1029,9 @@
 "/    sendButton destroy.
 
     updateButton := Button
-                        label:(resources at:'update')
-                        action:[self updateContext]
-                        in:bpanel.
+			label:(resources at:'update')
+			action:[self updateContext]
+			in:bpanel.
     monitorToggle := Toggle in:bpanel.
     monitorToggle label:(resources at:'monitor').
     monitorToggle pressAction:[self autoUpdateOn].
@@ -1051,33 +1051,33 @@
 "/    restartButton disable.
 
     aProcess isNil ifTrue:[
-        terminateButton disable.
-        abortButton disable.
-        continueButton disable.
-        returnButton disable.
-        restartButton disable.
+	terminateButton disable.
+	abortButton disable.
+	continueButton disable.
+	returnButton disable.
+	restartButton disable.
     ] ifFalse:[
-        (aProcess suspendedContext isNil 
-        or:[aProcess isSystemProcess]) ifTrue:[
-            terminateButton disable.
-        ].
-
-        self setContextSkippingInterruptContexts:aProcess suspendedContext.
-
-        catchBlock := [
-            catchBlock := nil.
-            contextArray := nil.
-            selectedContext := actualContext := firstContext := nil.
-            steppedContext := wrapperContext := nil.
-
-            (exitAction == #terminate) ifTrue:[
-                aProcess terminate.
-            ].
-            (exitAction == #quickTerminate) ifTrue:[
-                aProcess terminateNoSignal.
-            ].
-            super destroy
-        ].
+	(aProcess suspendedContext isNil 
+	or:[aProcess isSystemProcess]) ifTrue:[
+	    terminateButton disable.
+	].
+
+	self setContextSkippingInterruptContexts:aProcess suspendedContext.
+
+	catchBlock := [
+	    catchBlock := nil.
+	    contextArray := nil.
+	    selectedContext := actualContext := firstContext := nil.
+	    steppedContext := wrapperContext := nil.
+
+	    (exitAction == #terminate) ifTrue:[
+		aProcess terminate.
+	    ].
+	    (exitAction == #quickTerminate) ifTrue:[
+		aProcess terminateNoSignal.
+	    ].
+	    super destroy
+	].
     ].
     self open
 
@@ -1091,66 +1091,66 @@
     |s|
 
     aComponent == abortButton ifTrue:[
-        s := 'HELP_ABORT'
+	s := 'HELP_ABORT'
     ].
     aComponent == terminateButton ifTrue:[
-        s := 'HELP_TERMINATE'
+	s := 'HELP_TERMINATE'
     ].
     aComponent == continueButton ifTrue:[
-        continueButton label = (resources string:'stop') ifTrue:[
-            s := 'HELP_STOP'
-        ] ifFalse:[
-            s := 'HELP_CONTINUE'
-        ]
+	continueButton label = (resources string:'stop') ifTrue:[
+	    s := 'HELP_STOP'
+	] ifFalse:[
+	    s := 'HELP_CONTINUE'
+	]
     ].
     aComponent == stepButton ifTrue:[
-        s := 'HELP_STEP'
+	s := 'HELP_STEP'
     ].
     aComponent == nextButton ifTrue:[
-        s := 'HELP_NEXT'
+	s := 'HELP_NEXT'
     ].
     aComponent == nextOverButton ifTrue:[
-        s := 'HELP_NEXTOVER'
+	s := 'HELP_NEXTOVER'
     ].
     aComponent == nextOutButton ifTrue:[
-        s := 'HELP_NEXTOUT'
+	s := 'HELP_NEXTOUT'
     ].
     aComponent == stepButton ifTrue:[
-        s := 'HELP_STEP'
+	s := 'HELP_STEP'
     ].
     aComponent == sendButton ifTrue:[
-        s := 'HELP_SEND'
+	s := 'HELP_SEND'
     ].
     aComponent == returnButton ifTrue:[
-        s := 'HELP_RETURN'
+	s := 'HELP_RETURN'
     ].
     aComponent == restartButton ifTrue:[
-        s := 'HELP_RESTART'
+	s := 'HELP_RESTART'
     ].
     aComponent == contextView ifTrue:[
-        s := 'HELP_WALKBACK'
+	s := 'HELP_WALKBACK'
     ].
     aComponent == codeView ifTrue:[
-        s := 'HELP_CODEVIEW'
+	s := 'HELP_CODEVIEW'
     ].
     aComponent == monitorToggle ifTrue:[
-        s := 'HELP_MONITOR'
+	s := 'HELP_MONITOR'
     ].
     aComponent == updateButton ifTrue:[
-        s := 'HELP_UPDATE'
+	s := 'HELP_UPDATE'
     ].
 "/    aComponent == stopButton ifTrue:[
 "/        s := 'HELP_STOP'
 "/    ].
     (aComponent isComponentOf:receiverInspector) ifTrue:[
-        s := 'HELP_REC_INSP'
+	s := 'HELP_REC_INSP'
     ].
     (aComponent isComponentOf:contextInspector) ifTrue:[
-        s := 'HELP_CON_INSP'
+	s := 'HELP_CON_INSP'
     ].
 
     s notNil ifTrue:[
-        ^ resources string:s
+	^ resources string:s
     ].
     ^ nil
 
@@ -1187,86 +1187,86 @@
     bpanel := HorizontalPanelView
 "/                        origin:(0.0 @ 0.0)
 "/                        extent:(1.0 @ (font height * 2))
-                            in:self.
+			    in:self.
     bpanel horizontalLayout:#leftSpace.
     bpanel verticalLayout:#centerMax.
     bpanel verticalSpace:ViewSpacing // 2.
 
     terminateButton := Button
-                        label:(resources at:'terminate')
-                        action:[terminateButton turnOffWithoutRedraw. self doTerminate]
-                        in:bpanel.
+			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.
+			label:(resources at:'abort')
+			action:[abortButton turnOffWithoutRedraw. self doAbort]
+			in:bpanel.
     returnButton := Button
-                        label:(resources at:'return')
-                        action:[returnButton turnOff. self doReturn]
-                        in:bpanel.
+			label:(resources at:'return')
+			action:[returnButton turnOff. self doReturn]
+			in:bpanel.
 
     restartButton := Button
-                        label:(resources at:'restart')
-                        action:[restartButton turnOff. self doRestart]
-                        in:bpanel.
+			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.
+			label:(resources at:'continue')
+			action:[continueButton turnOffWithoutRedraw. self doContinue]
+			in:bpanel.
 
     separator := View extent:(10 @ 5) in:bpanel.
     separator borderWidth:0; level:0.
 
     img := Image fromFile:'bitmaps/stepIn.xpm'.
     img isNil ifTrue:[
-        img := (resources at:'next')
+	img := (resources at:'next')
     ].
     nextButton := Button
-                        label:img
-                        action:[stepButton turnOff. self doNext]
-                        in:bpanel.
+			label:img
+			action:[stepButton turnOff. self doNext]
+			in:bpanel.
 
     img := Image fromFile:'bitmaps/stepOver.xpm'.
     img isNil ifTrue:[
-        img := (resources at:'over')
+	img := (resources at:'over')
     ].
     nextOverButton := Button
-                        label:img
-                        action:[stepButton turnOff. self doNextOver]
-                        in:bpanel.
+			label:img
+			action:[stepButton turnOff. self doNextOver]
+			in:bpanel.
 
     img := Image fromFile:'bitmaps/stepOut.xpm'.
     img isNil ifTrue:[
-        img := (resources at:'out')
+	img := (resources at:'out')
     ].
     nextOutButton := Button
-                        label:img
-                        action:[stepButton turnOff. self doNextOut]
-                        in:bpanel.
+			label:img
+			action:[stepButton turnOff. self doNextOut]
+			in:bpanel.
 
     stepButton := Button
-                        label:(resources at:'step')
-                        action:[stepButton turnOff. self doStep]
-                        in:bpanel.
+			label:(resources at:'step')
+			action:[stepButton turnOff. self doStep]
+			in:bpanel.
     sendButton := Button
-                        label:(resources at:'send')
-                        action:[sendButton turnOff. self doSend]
-                        in:bpanel.
+			label:(resources at:'send')
+			action:[sendButton turnOff. self doSend]
+			in:bpanel.
 
     bpanel origin:(0.0 @ 0.0)
-           extent:(1.0 @ (bpanel preferredExtent y)).
+	   extent:(1.0 @ (bpanel preferredExtent y)).
 
     panel := VariableVerticalPanel
-                        origin:(0.0 @ bpanel height)
-                        corner:(1.0 @ 1.0)
-                            in:self.
+			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).
@@ -1276,10 +1276,10 @@
     contextView doubleClickAction:[:line | self browse].
 
     v := HVScrollableView 
-                for:CodeView 
-                miniScrollerH:true
-                miniScrollerV:false
-                 in:panel.
+		for:CodeView 
+		miniScrollerH:true
+		miniScrollerV:false
+		 in:panel.
     v origin:(0.0 @ 0.25) corner:(1.0 @ 0.75).
     v autoHideScrollBars:true.
     codeView := v scrolledView.
@@ -1288,13 +1288,13 @@
     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.
+				origin:(0.0 @ 0.0) corner:(0.5 @ 1.0)
+				    in:hpanel.
     receiverInspector label:'receiver'.
 
     contextInspector := ContextInspectorView
-                                origin:(0.5 @ 0.0) corner:(1.0 @ 1.0)
-                                    in:hpanel.
+				origin:(0.5 @ 0.0) corner:(1.0 @ 1.0)
+				    in:hpanel.
     contextInspector label:'context'.
 
     "Modified: / 31.10.1997 / 03:01:25 / cg"
@@ -1306,127 +1306,127 @@
     |labels selectors m|
 
     exclusive ifTrue:[
-        labels := resources array:#(
-                                    'show more'
-                                    'show verbose backtrace'
-                                    '-'
-                                    'remove breakpoint'
-                                    'remove all trace & breakpoints'
-                                    '-'
-                                    'copy walkback text'
-                                    '-'
-                                    'quickTerminate'
-                                    '='
-                                    'exit smalltalk (no confirmation)'
-                                  ).
-        selectors := #(
-                                 showMore
-                                 showVerboseBacktrace
-                                 nil
-                                 removeBreakpoint
-                                 removeAllBreakpoints
-                                 nil
-                                 copyWalkbackText
-                                 nil
-                                 quickTerminate
-                                 nil
-                                 exit
-                      )
+	labels := resources array:#(
+				    'show more'
+				    'show verbose backtrace'
+				    '-'
+				    'remove breakpoint'
+				    'remove all trace & breakpoints'
+				    '-'
+				    'copy walkback text'
+				    '-'
+				    'quickTerminate'
+				    '='
+				    'exit smalltalk (no confirmation)'
+				  ).
+	selectors := #(
+				 showMore
+				 showVerboseBacktrace
+				 nil
+				 removeBreakpoint
+				 removeAllBreakpoints
+				 nil
+				 copyWalkbackText
+				 nil
+				 quickTerminate
+				 nil
+				 exit
+		      )
     ] ifFalse:[
-        labels := resources array:#(
-                                    'show more'
-                                    'show verbose backtrace'
-                                    '-'
-                                    'skip'
-                                    'step out'
-                                    '-'
+	labels := resources array:#(
+				    'show more'
+				    'show verbose backtrace'
+				    '-'
+				    'skip'
+				    'step out'
+				    '-'
 "
-                                    'continue'
-                                    'terminate'
-                                    'abort'
-                                    '-'
-                                    'step'
-                                    'send'
-                                    '-'
-                                    'return'
-                                    'restart'
-                                    '-'
+				    '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
-                                         showVerboseBacktrace
-                                         nil
-                                         skip
-                                         skipForReturn
-                                         nil
+				    '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
+					 showVerboseBacktrace
+					 nil
+					 skip
+					 skipForReturn
+					 nil
 "
-                                         doContinue
-                                         doTerminate
-                                         doAbort
-                                         nil
-                                         doStep
-                                         doSend
-                                         nil
-                                         doReturn
-                                         doRestart
-                                         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
-        ).
+					 removeBreakpoint
+					 removeAllBreakpoints
+					 nil
+					 browse
+					 browseClass
+					 browseClassHierarchy
+					 browseFullClassProtocol
+					 implementors
+					 senders
+					 nil
+					 inspectContext
+					 copyWalkbackText
+					 nil
+					 quickTerminate
+					 nil
+					 exit
+	).
     ].
 
     m := PopUpMenu 
-                labels:(resources array:labels)
-             selectors:selectors
-              receiver:self
-                   for:contextView.
+		labels:(resources array:labels)
+	     selectors:selectors
+	      receiver:self
+		   for:contextView.
 
     verboseBacktrace ifTrue:[
-        m labelAt:#showVerboseBacktrace put:(resources string:'show dense backtrace').
-        m selectorAt:#showVerboseBacktrace put:#showDenseBacktrace
+	m labelAt:#showVerboseBacktrace put:(resources string:'show dense backtrace').
+	m selectorAt:#showVerboseBacktrace put:#showDenseBacktrace
     ].
 
     contextView middleButtonMenu:m. 
 
     inspecting ifTrue:[
-        m notNil ifTrue:[
-            m disableAll:#(doTraceStep removeBreakpoint browse browseClass
-                           browseClassHierarchy browseFullClassProtocol
-                           implementors senders inspectContext skip doStepOut).
-        ].
+	m notNil ifTrue:[
+	    m disableAll:#(doTraceStep removeBreakpoint browse browseClass
+			   browseClassHierarchy browseFullClassProtocol
+			   implementors senders inspectContext skip doStepOut).
+	].
     ]
 
     "Modified: / 29.10.1997 / 03:40:16 / cg"
@@ -1436,14 +1436,14 @@
     super postRealize.
 
     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).
-        ]
+	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).
+	]
     ]
 
     "Created: 24.7.1997 / 18:17:44 / cg"
@@ -1454,13 +1454,13 @@
 
     l := aMessage , ' ('.
     Object errorSignal handle:[:ex |
-        l := l , '???'
+	l := l , '???'
     ] do:[
-        nm := aProcess name.
-        nm notNil ifTrue:[
-            l := l , (nm contractTo:17) , ''.
-        ].
-        l := l , '[' , aProcess id printString , ']'.
+	nm := aProcess name.
+	nm notNil ifTrue:[
+	    l := l , (nm contractTo:17) , ''.
+	].
+	l := l , '[' , aProcess id printString , ']'.
     ].
     l := l , ')'.
     self label:l.
@@ -1470,7 +1470,7 @@
 
 contextInterrupt
     DebuggingDebugger == true ifTrue:[
-        'contextIRQ' printCR.
+	'contextIRQ' printCR.
     ].
     ^ self stepOrNext
 
@@ -1479,7 +1479,7 @@
 
 stepInterrupt
     DebuggingDebugger == true ifTrue:[
-        'stepIRQ' printCR.
+	'stepIRQ' printCR.
     ].
     ^ self stepOrNext
 
@@ -1496,13 +1496,13 @@
     "/ DebuggingDebugger := false
 
     skipLineNr == #return ifTrue:[
-        name := Processor activeProcess nameOrId.
-        self label:('stepping context returned ' , ' (process: ' , name , ')').
-        here := thisContext sender sender.
-        here setLineNumber:nil.
-        here := nil.
-        self enter:(thisContext sender sender sender) select:nil.
-        ^ self
+	name := Processor activeProcess nameOrId.
+	self label:('stepping context returned ' , ' (process: ' , name , ')').
+	here := thisContext sender sender.
+	here setLineNumber:nil.
+	here := nil.
+	self enter:(thisContext sender sender sender) select:nil.
+	^ self
     ].
 
 "/    "/
@@ -1515,8 +1515,8 @@
 "/    ].
 
     Processor activeProcess ~~ inspectedProcess ifTrue:[
-        'DebugView [info]: stray step interrupt' infoPrintCR.
-        ^ self
+	'DebugView [info]: stray step interrupt' infoPrintCR.
+	^ self
     ].
 
     here := thisContext.        "stepInterrupt"
@@ -1524,17 +1524,17 @@
     here := here sender.        "the interrupted context"  
 
     DebuggingDebugger == true ifTrue:[
-        '*******' printNL.
-        'here in ' print.
-        inWrap ifTrue:['(wrap) ' print.].
-        ((ObjectMemory addressOf:here) printStringRadix:16) print. ' ' print.
-        here selector printNL.
+	'*******' printNL.
+	'here in ' print.
+	inWrap ifTrue:['(wrap) ' print.].
+	((ObjectMemory addressOf:here) printStringRadix:16) print. ' ' print.
+	here selector printNL.
     ].
 
     "
      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
+	 check if we are in a wrapper methods hidden setup-sequence
+	 if so, ignore the interrupt and continue single sending
     "
     isWrap := false.
     left := false.
@@ -1542,63 +1542,63 @@
 
     where := here.
     inWrap ifTrue:[
-        wrappedMethod := nil.
-        5 timesRepeat:[
-            (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.
-                        lastWrappedContext := where.
-                        where sender receiver == method originalMethod ifFalse:[
-                            isWrap := true.
-                        ]
-                    ] ifFalse:[
-                        where == steppedContext ifTrue:[
-
-                            DebuggingDebugger == true ifTrue:[
-                                'change stepCon from: ' print.
-                                steppedContext print.
-                                ' to lastWrapped: ' print.
-                                lastWrappedContext printNL.
-                            ].
-
-                            inWrap := false.
-                            leftWrap := true.
-                            wrapperContext := steppedContext.
-                            steppedContext := lastWrappedContext
-                        ]
-                    ]
-                ].
-                where := where sender
-            ]
-        ].
+	wrappedMethod := nil.
+	5 timesRepeat:[
+	    (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.
+			lastWrappedContext := where.
+			where sender receiver == method originalMethod ifFalse:[
+			    isWrap := true.
+			]
+		    ] ifFalse:[
+			where == steppedContext ifTrue:[
+
+			    DebuggingDebugger == true ifTrue:[
+				'change stepCon from: ' print.
+				steppedContext print.
+				' to lastWrapped: ' print.
+				lastWrappedContext printNL.
+			    ].
+
+			    inWrap := false.
+			    leftWrap := true.
+			    wrapperContext := steppedContext.
+			    steppedContext := lastWrappedContext
+			]
+		    ]
+		].
+		where := where sender
+	    ]
+	].
     ].
 
     isWrap ifTrue:[
-        DebuggingDebugger == true ifTrue:[
-            'ignore wrap' printNL.
-        ].
-
-        "/
-        "/ ignore, while in wrappers hidden setup
-        "/
-        where := nil. here := nil.
-        ObjectMemory flushInlineCaches.
+	DebuggingDebugger == true ifTrue:[
+	    'ignore wrap' printNL.
+	].
+
+	"/
+	"/ ignore, while in wrappers hidden setup
+	"/
+	where := nil. here := nil.
+	ObjectMemory flushInlineCaches.
         
-        skipLineNr == #return ifTrue:[
-            DebuggingDebugger == true ifTrue:[
-                'skipRet in wrap' printCR.
-            ]
-        ].
-
-        StepInterruptPending := 1.
-        InterruptPending := 1.
-        InStepInterrupt := nil.
-        ^ nil
+	skipLineNr == #return ifTrue:[
+	    DebuggingDebugger == true ifTrue:[
+		'skipRet in wrap' printCR.
+	    ]
+	].
+
+	StepInterruptPending := 1.
+	InterruptPending := 1.
+	InStepInterrupt := nil.
+	^ nil
     ].
 
     inBlock := false.
@@ -1609,31 +1609,31 @@
     "/
     (bigStep 
     and:[steppedContext notNil]) ifTrue:[
-        "
-         a step or next - ignore all contexts below the interesting one
-        "
-        where := here.      "the interrupted context"
-        contextBelow := nil.
-
-        where home notNil ifTrue:[
-            "/
-            "/ in a block called by 'our' context ?
-            "/
-            where home == steppedContext ifTrue:[
+	"
+	 a step or next - ignore all contexts below the interesting one
+	"
+	where := here.      "the interrupted context"
+	contextBelow := nil.
+
+	where home notNil ifTrue:[
+	    "/
+	    "/ in a block called by 'our' context ?
+	    "/
+	    where home == steppedContext ifTrue:[
 "/ '*block*' printNL.
-                inBlock := true
-            ]
-        ].
-
-        where == steppedContext ifFalse:[
-            where := where sender.
-
-            where notNil ifTrue:[
-                where home == steppedContext ifTrue:[
+		inBlock := true
+	    ]
+	].
+
+	where == steppedContext ifFalse:[
+	    where := where sender.
+
+	    where notNil ifTrue:[
+		where home == steppedContext ifTrue:[
 "/ '*block*' printNL.
-                    inBlock := true.
-                ]
-            ].
+		    inBlock := true.
+		]
+	    ].
 
 "/ 'looking for ' print.
 "/  (steppedContextAddress printStringRadix:16)print. '' printNL.
@@ -1641,268 +1641,268 @@
 "/where print. ' ' print. ((ObjectMemory addressOf:where)printStringRadix:16) printCR.
 "/steppedContext print. ' ' print. ((ObjectMemory addressOf:steppedContext)printStringRadix:16) printCR.
 
-            where == steppedContext 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:[
-
-                        "/ if either the receiver or any arg of this context
-                        "/ is a block of the steppedContext, we must really
-                        "/ do a single step. Otherwise, stepping through a
-                        "/ do:-loop would be very difficult.
-
-                        (where receiver isBlock
-                        and:[where receiver home == steppedContext])
-                        ifTrue:[
-                            anyStepBlocks := true.
-                        ] ifFalse:[
-                            where args do:[:arg |
-                                (arg isBlock
-                                and:[arg home == steppedContext])
-                                ifTrue:[
-                                    anyStepBlocks := true.
-                                ]
-                            ]
-                        ].
-
-                        DebuggingDebugger == true ifTrue:[
-                            ((ObjectMemory addressOf:where) printStringRadix:16)print. ' ' print.
-                            where selector printNL.
-                        ].
-
-                        where == steppedContext ifTrue:[
+	    where == steppedContext 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:[
+
+			"/ if either the receiver or any arg of this context
+			"/ is a block of the steppedContext, we must really
+			"/ do a single step. Otherwise, stepping through a
+			"/ do:-loop would be very difficult.
+
+			(where receiver isBlock
+			and:[where receiver home == steppedContext])
+			ifTrue:[
+			    anyStepBlocks := true.
+			] ifFalse:[
+			    where args do:[:arg |
+				(arg isBlock
+				and:[arg home == steppedContext])
+				ifTrue:[
+				    anyStepBlocks := true.
+				]
+			    ]
+			].
+
+			DebuggingDebugger == true ifTrue:[
+			    ((ObjectMemory addressOf:where) printStringRadix:16)print. ' ' print.
+			    where selector printNL.
+			].
+
+			where == steppedContext 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
-                            ].
-                            "
-                              yes, a context below
-                              - continue and schedule another stepInterrupt.
-                              Must flush caches since optimized methods not always
-                              look for pending interrupts
-                            "
-
-                            contextBelow notNil ifTrue:[
+			    "
+			     found the interesting context somwehere up in the
+			     chain. We seem to be still below the interesting one ...
+			    "
+			    tracing == true ifTrue:[
+				here printString printCR
+			    ].
+			    "
+			      yes, a context below
+			      - continue and schedule another stepInterrupt.
+			      Must flush caches since optimized methods not always
+			      look for pending interrupts
+			    "
+
+			    contextBelow notNil ifTrue:[
 "/ 'prepare for unwind-catch' printNL.
 "/ 'con= ' print. contextBelow printCR.
-                                contextBelow selector notNil ifTrue:[
-                                    self label:'single stepping - please wait ...(' , contextBelow selector , ')'.
-                                ].
-
-                                DebuggingDebugger == true ifTrue:[
-                                    'below stepCon; continue until unwind of: ' print.
-                                    contextBelow printCR.
-                                ].
-                                Processor activeProcess forceInterruptOnReturnOf:contextBelow.
-                                StepInterruptPending := nil.
-                            ] ifFalse:[
-                                ObjectMemory flushInlineCaches.
-
-                                here selector notNil ifTrue:[
-                                    self label:'single stepping - please wait ...(' , here selector , ')'.
-                                ].
-
-                                DebuggingDebugger == true ifTrue:[
-                                    'in stepCon; continue single stepping' printCR.
-                                ].
-                                StepInterruptPending := 1.
-                                InterruptPending := 1.
-                            ].
-                            where := nil. here := nil.
-                            InStepInterrupt := nil.
-
-                            ^ nil
-                        ].
-
-                        where methodHome == steppedContext methodHome ifTrue:[
-                            inBlock := true.
-                        ].
-
-                        anyStepBlocks ifFalse:[
-                            inBlock ifFalse:[
-                                contextBelow := where
-                            ]
-                        ].
-                        where := where sender
-                    ].
-                    s := 'context returned'.
-                    left := true.
-                ].
-            ] ifTrue:[
+				contextBelow selector notNil ifTrue:[
+				    self label:'single stepping - please wait ...(' , contextBelow selector , ')'.
+				].
+
+				DebuggingDebugger == true ifTrue:[
+				    'below stepCon; continue until unwind of: ' print.
+				    contextBelow printCR.
+				].
+				Processor activeProcess forceInterruptOnReturnOf:contextBelow.
+				StepInterruptPending := nil.
+			    ] ifFalse:[
+				ObjectMemory flushInlineCaches.
+
+				here selector notNil ifTrue:[
+				    self label:'single stepping - please wait ...(' , here selector , ')'.
+				].
+
+				DebuggingDebugger == true ifTrue:[
+				    'in stepCon; continue single stepping' printCR.
+				].
+				StepInterruptPending := 1.
+				InterruptPending := 1.
+			    ].
+			    where := nil. here := nil.
+			    InStepInterrupt := nil.
+
+			    ^ nil
+			].
+
+			where methodHome == steppedContext methodHome ifTrue:[
+			    inBlock := true.
+			].
+
+			anyStepBlocks ifFalse:[
+			    inBlock ifFalse:[
+				contextBelow := where
+			    ]
+			].
+			where := where sender
+		    ].
+		    s := 'context returned'.
+		    left := true.
+		].
+	    ] ifTrue:[
 "/ 'found it right in sender' printNL.
-                s := 'after step'
-            ].
-        ] ifTrue:[
+		s := 'after step'
+	    ].
+	] ifTrue:[
 "/ 'found it right away' printNL.
-            s := 'after step'
-        ].
+	    s := 'after step'
+	].
     ] ifFalse:[
 "/ ' send' printNL.
-        "
-         a send
-        "
-        DebuggingDebugger == true ifTrue:[
-            'clear steppedContext' printCR.
-        ].
-        steppedContext := nil.
-        s := 'after send'
+	"
+	 a send
+	"
+	DebuggingDebugger == true ifTrue:[
+	    'clear steppedContext' printCR.
+	].
+	steppedContext := nil.
+	s := 'after send'
     ].
 
     ignore := false.
     (inBlock and:[stepHow == #nextOver or:[stepHow == #nextOut]]) ifTrue:[
-        ignore := true.
+	ignore := true.
     ].
 
     "/ handle the case, when a subBlock leaves;
     "/ continue stepping in the home context.
 
     left ifTrue:[
-        steppedContext home notNil ifTrue:[
-            steppedContext := steppedContext home.
-            s := 'after step'.
-            left := false.
+	steppedContext home notNil ifTrue:[
+	    steppedContext := steppedContext home.
+	    s := 'after step'.
+	    left := false.
 "/ DebugView enterUnconditional:thisContext withMessage:'debug'.
 
-        ]
+	]
     ].
 
     "
      kludge to hide breakpoint wrappers in the context list: 
-         check if we are in a wrapper methods hidden exit-sequence
-         if so, ignore the interrupt and continue single sending
+	 check if we are in a wrapper methods hidden exit-sequence
+	 if so, ignore the interrupt and continue single sending
     "
     (where isNil 
     and:[wrapperContext notNil])
     ifTrue:[
-        "/ did not find our steppedContext along the chain;
-        "/ could be in a wrappedMethods exitBlock ...
-
-        leftWrap ifFalse:[
-            where := here.
-            wrappedMethod := nil.
-            5 timesRepeat:[
-                where notNil ifTrue:[
-                    where isBlockContext ifFalse:[
-                        method := where method.
-                        (method notNil and:[method isWrapped]) ifTrue:[
-                            where == wrapperContext ifTrue:[
-                                DebuggingDebugger == true ifTrue:[
-                                    'change stepCon fromWrapped: ' print.
-                                    steppedContext print.
-                                    ' to: ' print.
-                                    wrapperContext printNL.
-                                ].
-
-                                inWrap := true.
-                                enteredWrap := true.
-                                steppedContext := wrapperContext.
-                                wrapperContext := nil.
-                            ]
-                        ].
-                    ].
-                    where := where sender
-                ]
-            ].
-        ].
-        enteredWrap ifTrue:[
-            ignore := true
-        ]
+	"/ did not find our steppedContext along the chain;
+	"/ could be in a wrappedMethods exitBlock ...
+
+	leftWrap ifFalse:[
+	    where := here.
+	    wrappedMethod := nil.
+	    5 timesRepeat:[
+		where notNil ifTrue:[
+		    where isBlockContext ifFalse:[
+			method := where method.
+			(method notNil and:[method isWrapped]) ifTrue:[
+			    where == wrapperContext ifTrue:[
+				DebuggingDebugger == true ifTrue:[
+				    'change stepCon fromWrapped: ' print.
+				    steppedContext print.
+				    ' to: ' print.
+				    wrapperContext printNL.
+				].
+
+				inWrap := true.
+				enteredWrap := true.
+				steppedContext := wrapperContext.
+				wrapperContext := nil.
+			    ]
+			].
+		    ].
+		    where := where sender
+		]
+	    ].
+	].
+	enteredWrap ifTrue:[
+	    ignore := true
+	]
     ].
 
     "/
 
     left ifTrue:[
-        "/ special care for stepInterrupt in send,
-        "/ when created a dummy context (lineNr == 1)
-
-        steppedContext lineNumber isNil ifTrue:[
-            steppedContext selector == here sender selector ifTrue:[
-                left := false.
-                s := 'after step'.
-                steppedContext := here sender.
-            ].
-        ].
-        oneMore := true
+	"/ special care for stepInterrupt in send,
+	"/ when created a dummy context (lineNr == 1)
+
+	steppedContext lineNumber isNil ifTrue:[
+	    steppedContext selector == here sender selector ifTrue:[
+		left := false.
+		s := 'after step'.
+		steppedContext := here sender.
+	    ].
+	].
+	oneMore := true
     ].
 
     inBlock ifTrue:[
 "/ 'inBlock' printNL.
-        s := 'in block'.
+	s := 'in block'.
     ].
 
     DebuggingDebugger == true ifTrue:[
-        where notNil ifTrue:[
-            '(' print. steppedContextLineno print. ') ' print.
-            where print.
-            '[' print. where lineNumber print. ']' printNL.
-        ].
+	where notNil ifTrue:[
+	    '(' print. steppedContextLineno print. ') ' print.
+	    where print.
+	    '[' print. where lineNumber print. ']' printNL.
+	].
     ].
 
     ignore ifFalse:[
-        (bigStep 
-        and:[steppedContextLineno notNil 
-        and:[where notNil 
-        and:[where lineNumber == steppedContextLineno]]]) ifTrue:[
-            (here isBlockContext 
-            and:[(here methodHome == steppedContext)
-                 or:[here home == steppedContext]]) ifTrue:[
-                DebuggingDebugger == true ifTrue:[
-                    'same line but in block' printNL.
-                ].
-
-                steppedContext := actualContext := here.
-                steppedContextLineno := here lineNumber.
-            ] ifFalse:[    
-                DebuggingDebugger == true ifTrue:[
-                    'same line - ignored' printNL.
-                ].
-                ignore := true
-            ].
-        ].
-
-        (left not 
-        and:[skipLineNr notNil 
-        and:[where notNil
-        and:[where lineNumber < skipLineNr]]]) ifTrue:[
-            DebuggingDebugger == true ifTrue:[
-                'skip (' print. skipLineNr print. ' unreached - ignored' printNL.
-            ].
-            ignore := true
-        ].
-
-        (steppedContextLineno isNil 
-        and:[skipLineNr isNil
-        and:[thisContext sender selector == #contextInterrupt]]) ifTrue:[
-            DebuggingDebugger == true ifTrue:[
-                'same line2 (after conIRQ) - ignored' printNL.
-            ].
-            ignore := true
-        ].
+	(bigStep 
+	and:[steppedContextLineno notNil 
+	and:[where notNil 
+	and:[where lineNumber == steppedContextLineno]]]) ifTrue:[
+	    (here isBlockContext 
+	    and:[(here methodHome == steppedContext)
+		 or:[here home == steppedContext]]) ifTrue:[
+		DebuggingDebugger == true ifTrue:[
+		    'same line but in block' printNL.
+		].
+
+		steppedContext := actualContext := here.
+		steppedContextLineno := here lineNumber.
+	    ] ifFalse:[    
+		DebuggingDebugger == true ifTrue:[
+		    'same line - ignored' printNL.
+		].
+		ignore := true
+	    ].
+	].
+
+	(left not 
+	and:[skipLineNr notNil 
+	and:[where notNil
+	and:[where lineNumber < skipLineNr]]]) ifTrue:[
+	    DebuggingDebugger == true ifTrue:[
+		'skip (' print. skipLineNr print. ' unreached - ignored' printNL.
+	    ].
+	    ignore := true
+	].
+
+	(steppedContextLineno isNil 
+	and:[skipLineNr isNil
+	and:[thisContext sender selector == #contextInterrupt]]) ifTrue:[
+	    DebuggingDebugger == true ifTrue:[
+		'same line2 (after conIRQ) - 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
+	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.
@@ -1918,16 +1918,16 @@
 "/'enter' printCR.
 
     DebuggingDebugger == true ifTrue:[
-        '==> enter on: ' print. thisContext sender sender printCR.
+	'==> enter on: ' print. thisContext sender sender printCR.
     ].
 
     initiallyShown := nil.
     (oneMore == true) ifTrue:[
-        thisContext sender sender lineNumber <= 1 ifTrue:[
-            initiallyShown := 2
-        ] ifFalse:[
-            initiallyShown := 1
-        ]
+	thisContext sender sender lineNumber <= 1 ifTrue:[
+	    initiallyShown := 2
+	] ifFalse:[
+	    initiallyShown := 1
+	]
     ].
     self enter:(thisContext sender sender) select:initiallyShown
 
@@ -1979,15 +1979,15 @@
 
     mthd := selectedContext method.
     mthd notNil ifTrue:[
-        who := selectedContext method who.
-        who notNil ifTrue:[
-            cls := who methodClass.
-            sel := who methodSelector.
-        ]
+	who := selectedContext method who.
+	who notNil ifTrue:[
+	    cls := who methodClass.
+	    sel := who methodSelector.
+	]
     ].
     cls isNil ifTrue:[
-        "/ class not found - try receiver
-        cls := selectedContext receiver class
+	"/ class not found - try receiver
+	cls := selectedContext receiver class
     ].
 
     cls browserClass openInClass:cls selector:sel.
@@ -2038,16 +2038,16 @@
      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
+	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
     ].
 
     steppedContext := wrapperContext := nil.
@@ -2056,11 +2056,11 @@
 
     "exit private event-loop"
     catchBlock notNil ifTrue:[
-        abortButton turnOff.
-        catchBlock value.
-
-        "/ not reached
-        'DebugView [warning]: abort failed' errorPrintCR.
+	abortButton turnOff.
+	catchBlock value.
+
+	"/ not reached
+	'DebugView [warning]: abort failed' errorPrintCR.
     ].
 
     ^ self.
@@ -2072,35 +2072,35 @@
     "continue from menu"
 
     inspecting ifTrue:[
-        device hasColors ifTrue:[
-            continueButton foregroundColor:Color red darkened.
-        ].
-        continueButton label:(resources string:'stop').
-        continueButton action:[self doStop].
-
-        self processPerform:#resume.
-
-        ^ self
+	device hasColors ifTrue:[
+	    continueButton foregroundColor:Color red darkened.
+	].
+	continueButton label:(resources string:'stop').
+	continueButton action:[self doStop].
+
+	self processPerform:#resume.
+
+	^ self
     ].
     canContinue ifTrue:[
-        steppedContext := wrapperContext := nil.
-        tracing := false.
-        haveControl := false.
-        exitAction := #continue.
-
-        "exit private event-loop"
-        catchBlock notNil ifTrue:[catchBlock value].
-
-        "/ not reached.
-        'DebugView [warning]: continue failed' errorPrintCR.
-        continueButton turnOff.
+	steppedContext := wrapperContext := nil.
+	tracing := false.
+	haveControl := false.
+	exitAction := #continue.
+
+	"exit private event-loop"
+	catchBlock notNil ifTrue:[catchBlock value].
+
+	"/ not reached.
+	'DebugView [warning]: continue failed' errorPrintCR.
+	continueButton turnOff.
 
     ] ifFalse:[
-        inspecting ifFalse:[
-            'DebugView [info]: resuming top context' infoPrintCR.
-            self showSelection:1.
-            self doReturn
-        ]
+	inspecting ifFalse:[
+	    'DebugView [info]: resuming top context' infoPrintCR.
+	    self showSelection:1.
+	    self doReturn
+	]
     ]
 
     "Modified: 10.1.1997 / 17:38:34 / cg"
@@ -2112,16 +2112,16 @@
     inspecting ifTrue:[^ self].
 
     canContinue ifTrue:[
-        steppedContext := wrapperContext := nil.
-        haveControl := false.
-        exitAction := #step.
-
-        "exit private event-loop"
-        catchBlock notNil ifTrue:[catchBlock value].
-
-        "/ not reached
-        'DebugView [warning]: send failed' errorPrintCR.
-        sendButton turnOff.
+	steppedContext := wrapperContext := nil.
+	haveControl := false.
+	exitAction := #step.
+
+	"exit private event-loop"
+	catchBlock notNil ifTrue:[catchBlock value].
+
+	"/ not reached
+	'DebugView [warning]: send failed' errorPrintCR.
+	sendButton turnOff.
     ]
 
     "Modified: 10.1.1997 / 17:38:41 / cg"
@@ -2169,11 +2169,11 @@
     "restart - the selected context will be restarted"
 
     inspecting ifTrue:[
-        selectedContext isNil ifTrue:[
-            ^ self showError:'** select a context first **'
-        ].
-        self interruptProcessWith:[selectedContext unwindAndRestart].
-        ^ self
+	selectedContext isNil ifTrue:[
+	    ^ self showError:'** select a context first **'
+	].
+	self interruptProcessWith:[selectedContext unwindAndRestart].
+	^ self
     ].
 
     steppedContext := wrapperContext := nil.
@@ -2194,11 +2194,11 @@
     "return - the selected context will do a ^nil"
 
     inspecting ifTrue:[
-        selectedContext isNil ifTrue:[
-            ^ self showError:'** select a context first **'
-        ].
-        self interruptProcessWith:[selectedContext unwind].
-        ^ self
+	selectedContext isNil ifTrue:[
+	    ^ self showError:'** select a context first **'
+	].
+	self interruptProcessWith:[selectedContext unwind].
+	^ self
     ].
 
     steppedContext := wrapperContext := nil.
@@ -2258,60 +2258,60 @@
     inspecting ifTrue:[^ self].
 
     canContinue ifTrue:[
-        selectedContext notNil ifTrue:[
-            con := actualContext. "/ selectedContext.
-            steppedContextLineno := actualContext lineNumber.
-        ] ifFalse:[
-            con := contextArray at:2.
-            steppedContextLineno := con lineNumber.
-        ].
-
-        skipLineNr := lineNr.
-
-        lineNr == -1 ifTrue:[
-            steppedContextLineno := skipLineNr := nil.
-        ].
-
-        stepHow == #send ifTrue:[
-            steppedContext := contextArray at:1.
-            stepHow := #nextIn.
-        ] ifFalse:[
-            stepHow == #nextOut ifTrue:[
-                steppedContext := con home.
-            ] ifFalse:[
-                steppedContext := con.
-            ].
-        ].
-        wrapperContext := nil.
+	selectedContext notNil ifTrue:[
+	    con := actualContext. "/ selectedContext.
+	    steppedContextLineno := actualContext lineNumber.
+	] ifFalse:[
+	    con := contextArray at:2.
+	    steppedContextLineno := con lineNumber.
+	].
+
+	skipLineNr := lineNr.
+
+	lineNr == -1 ifTrue:[
+	    steppedContextLineno := skipLineNr := nil.
+	].
+
+	stepHow == #send ifTrue:[
+	    steppedContext := contextArray at:1.
+	    stepHow := #nextIn.
+	] ifFalse:[
+	    stepHow == #nextOut ifTrue:[
+		steppedContext := con home.
+	    ] ifFalse:[
+		steppedContext := con.
+	    ].
+	].
+	wrapperContext := nil.
 
 "/ ' step con:' print. (ObjectMemory addressOf:steppedContext) printHex. ' ' print. steppedContext printCR.
 
-        "
-         if we step in a wrapped method,
-         prepare to skip the prolog ...
-        "
-
-        inWrap := false.
-        method := con method.
-        (method notNil and:[method isWrapped]) ifTrue:[
-            inWrap := true
-        ].
-
-        lineNr == #return ifTrue:[
-            Processor activeProcess forceInterruptOnReturnOf:con.
-        ].
-
-        con := nil.
-        bigStep := true.
-        haveControl := false.
-        exitAction := #step.
-
-        "exit private event-loop"
-        catchBlock notNil ifTrue:[catchBlock value].
-
-        "/ not reached
-        'DebugView [warning]: step failed' errorPrintCR.
-        stepButton turnOff. nextButton turnOff. sendButton turnOff.
+	"
+	 if we step in a wrapped method,
+	 prepare to skip the prolog ...
+	"
+
+	inWrap := false.
+	method := con method.
+	(method notNil and:[method isWrapped]) ifTrue:[
+	    inWrap := true
+	].
+
+	lineNr == #return ifTrue:[
+	    Processor activeProcess forceInterruptOnReturnOf:con.
+	].
+
+	con := nil.
+	bigStep := true.
+	haveControl := false.
+	exitAction := #step.
+
+	"exit private event-loop"
+	catchBlock notNil ifTrue:[catchBlock value].
+
+	"/ not reached
+	'DebugView [warning]: step failed' errorPrintCR.
+	stepButton turnOff. nextButton turnOff. sendButton turnOff.
     ]
 
     "Modified: 6.3.1997 / 21:11:38 / cg"
@@ -2321,15 +2321,15 @@
     "stop the process (if its running, otherwise this is a no-op)"
 
     inspecting ifTrue:[
-        device hasColors ifTrue:[
-            continueButton foregroundColor:Color green darkened darkened.
-        ].
-        continueButton label:(resources string:'continue').
-        continueButton action:[self doContinue].
-
-        self processPerform:#stop.
-
-        ^ self
+	device hasColors ifTrue:[
+	    continueButton foregroundColor:Color green darkened darkened.
+	].
+	continueButton label:(resources string:'continue').
+	continueButton action:[self doContinue].
+
+	self processPerform:#stop.
+
+	^ self
     ].
 
     "Modified: 20.10.1996 / 18:30:48 / cg"
@@ -2339,8 +2339,8 @@
     "terminate - the process has a chance for cleanup"
 
     inspecting ifTrue:[
-        self processPerform:#terminate.
-        ^ self
+	self processPerform:#terminate.
+	^ self
     ].
 
     steppedContext := wrapperContext := nil.
@@ -2352,8 +2352,8 @@
 
     "/ not reached (normally)
     inspecting ifFalse:[
-        'DebugView [warning]: terminate failed' errorPrintCR.
-        self warn:'terminate failed'.
+	'DebugView [warning]: terminate failed' errorPrintCR.
+	self warn:'terminate failed'.
     ].
     terminateButton turnOff.
 
@@ -2427,8 +2427,8 @@
     "quick terminate - the process will get no chance for cleanup actions"
 
     inspecting ifTrue:[
-        self processPerform:#terminateNoSignal.
-        ^ self
+	self processPerform:#terminateNoSignal.
+	^ self
     ].
 
     steppedContext := wrapperContext := nil.
@@ -2440,8 +2440,8 @@
 
     "/ not reached (normally)
     inspecting ifFalse:[
-        'DebugView [warning]: terminate failed' errorPrintCR.
-        self warn:'terminate failed'.
+	'DebugView [warning]: terminate failed' errorPrintCR.
+	self warn:'terminate failed'.
     ].
     terminateButton turnOff.
 
@@ -2452,7 +2452,7 @@
     "remove all trace & breakpoints - if any"
 
     (MessageTracer notNil and:[MessageTracer isLoaded]) ifTrue:[
-        MessageTracer unwrapAllMethods
+	MessageTracer unwrapAllMethods
     ]
 
     "Modified: 21.9.1997 / 11:38:23 / cg"
@@ -2464,18 +2464,18 @@
     |implementorClass method|
 
     selectedContext isNil ifTrue:[
-        ^ self showError:'** select a context first **'
+	^ self showError:'** select a context first **'
     ].
     (MessageTracer isNil or:[MessageTracer isLoaded not]) ifTrue:[
-        ^ self
+	^ self
     ].
 
     implementorClass := selectedContext methodClass. 
     implementorClass notNil ifTrue:[
-        method := implementorClass compiledMethodAt:selectedContext selector.
-        (method notNil and:[method isWrapped]) ifTrue:[
-            MessageTracer unwrapMethod:method
-        ]
+	method := implementorClass compiledMethodAt:selectedContext selector.
+	(method notNil and:[method isWrapped]) ifTrue:[
+	    MessageTracer unwrapMethod:method
+	]
     ].
     contextView middleButtonMenu disable:#removeBreakpoint.
 
@@ -2505,8 +2505,8 @@
     "double number of contexts shown"
 
     contextArray notNil ifTrue:[
-        nChainShown := nChainShown * 2.
-        self redisplayBacktrace.
+	nChainShown := nChainShown * 2.
+	self redisplayBacktrace.
     ]
 
     "Modified: 12.1.1997 / 01:24:26 / cg"
@@ -2587,27 +2587,27 @@
     |oldSelection oldContext con idx|
 
     contextArray notNil ifTrue:[
-        self withWaitCursorDo:[
-            oldSelection := contextView selection.
-            oldSelection notNil ifTrue:[
-                oldContext := contextArray at:oldSelection ifAbsent:nil.
-            ].
-
-            con := firstContext.
+	self withWaitCursorDo:[
+	    oldSelection := contextView selection.
+	    oldSelection notNil ifTrue:[
+		oldContext := contextArray at:oldSelection ifAbsent:nil.
+	    ].
+
+	    con := firstContext.
 "/            con := contextArray at:1.
-            contextArray at:1 put:nil.
-            self setContext:con.
-
-            oldContext isNil ifTrue:[
-                idx := oldSelection
-            ] ifFalse:[
-                idx := contextArray identityIndexOf:oldContext ifAbsent:nil.
-            ].
-            contextView setSelection:idx.
-            idx notNil ifTrue:[
-                self showSelection:idx
-            ]
-        ]
+	    contextArray at:1 put:nil.
+	    self setContext:con.
+
+	    oldContext isNil ifTrue:[
+		idx := oldSelection
+	    ] ifFalse:[
+		idx := contextArray identityIndexOf:oldContext ifAbsent:nil.
+	    ].
+	    contextView setSelection:idx.
+	    idx notNil ifTrue:[
+		self showSelection:idx
+	    ]
+	]
     ]
 
     "Created: 10.1.1997 / 21:36:46 / cg"
@@ -2628,164 +2628,164 @@
     |con text method caller caller2 m count showIt c suspendContext nm h|
 
     (contextArray notNil and:[aContext == (contextArray at:1)]) ifTrue:[
-        "no change"
-        ^ false
+	"no change"
+	^ false
     ].
 
     firstContext := aContext.
 
     m := contextView middleButtonMenu.
     m notNil ifTrue:[
-        m disable:#showMore.
+	m disable:#showMore.
     ].
 
     aContext isNil ifTrue:[
-        text := Array with:'** no context **'.
-        contextArray := nil.
+	text := Array with:'** no context **'.
+	contextArray := nil.
     ] ifFalse:[
-        text := OrderedCollection new:nChainShown.
-        contextArray := OrderedCollection new:nChainShown.
-        con := aContext.
-
-        verboseBacktrace ~~ true ifTrue:[
-            "/ with dense backtrace, hide the ProcessorScheduler
-            "/ contexts at the top; look for a Process>>suspend*
-            "/ context within the first 10 contexts
-
-            suspendContext := nil.
-            c := con.
-            1 to:10 do:[:i |
-                |sel|
-
-                c notNil ifTrue:[
-                    (sel := c selector) notNil ifTrue:[
-                        ((sel isSymbol and:[sel startsWith:'suspend'])
-                        and:[c receiver isMemberOf:Process]) ifTrue:[
-                            suspendContext := c
-                        ].
-                    ].
-                    c := c sender.
-                ]
-            ].
-            suspendContext notNil ifTrue:[
-                con := suspendContext. suspendContext := nil
-            ].
-        ].
-
-        "
-         get them all
-        "
-        count := 0.
-        [con notNil and:[count <= nChainShown]] whileTrue:[
-
-            (self showingContext:con) ifTrue:[
-                contextArray add:con.
-
-                (MoreDebuggingDetail == true) ifTrue:[
-                    nm := (((ObjectMemory addressOf:con) printStringRadix:16) , ' ' , con printString).
-                ] ifFalse:[
-                    nm := con printString.
-                ].
-                text add:nm.
-                count := count + 1.
-            ].
-
-            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
-            ].
-
-            "/ with dense backtrace, skip the doIt methods context
-            "/ (its dummy anyway) and fake that contexts name
-
-            verboseBacktrace ~~ true ifTrue:[
-                (con isBlockContext
-                 and:[(h := con home) == con sender
-                 and:[((h selector == #doIt)
-                       or:[h selector == #doIt:])
-                 and:[h method who isNil]]]) ifTrue:[
-                    con := con sender.
-                    text removeLast.
-                    text add:(con methodHome printString)
-                ].
-                h := nil.  "/ never keep refs to contexts unless you really need them ...
-            ].
-
-            "/ and also, all lazy loading intermediates
-
-            verboseBacktrace ~~ true ifTrue:[
-                (con selector == #noByteCode 
-                and:[con receiver isMethod]) ifTrue:[
-                    contextArray removeLast.    
-                    text removeLast.
-                    con := con sender.
-                    count := count - 1.
-                ]
-            ].
-
-            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
-            ].
-
-            verboseBacktrace ~~ true ifTrue:[
-                "/ in dense mode, remove the process startup
-                "/ contexts (if any)
-
-                (con := contextArray last) methodClass == Process ifTrue:[
-                    con selector == #start ifTrue:[
-                        contextArray removeLast.
-                        text removeLast.
-
-                        [contextArray size > 0
-                         and:[contextArray last methodHome == con]] whileTrue:[
-                            contextArray removeLast.
-                            text removeLast.
-                        ]
-                    ]
-                ]
-            ]
-        ] ifFalse:[
-            m notNil ifTrue:[
-                m enable:#showMore.
-                text add:(resources string:'*** more walkback follows - click here to see them ***')
-            ].
-        ].
+	text := OrderedCollection new:nChainShown.
+	contextArray := OrderedCollection new:nChainShown.
+	con := aContext.
+
+	verboseBacktrace ~~ true ifTrue:[
+	    "/ with dense backtrace, hide the ProcessorScheduler
+	    "/ contexts at the top; look for a Process>>suspend*
+	    "/ context within the first 10 contexts
+
+	    suspendContext := nil.
+	    c := con.
+	    1 to:10 do:[:i |
+		|sel|
+
+		c notNil ifTrue:[
+		    (sel := c selector) notNil ifTrue:[
+			((sel isSymbol and:[sel startsWith:'suspend'])
+			and:[c receiver isMemberOf:Process]) ifTrue:[
+			    suspendContext := c
+			].
+		    ].
+		    c := c sender.
+		]
+	    ].
+	    suspendContext notNil ifTrue:[
+		con := suspendContext. suspendContext := nil
+	    ].
+	].
+
+	"
+	 get them all
+	"
+	count := 0.
+	[con notNil and:[count <= nChainShown]] whileTrue:[
+
+	    (self showingContext:con) ifTrue:[
+		contextArray add:con.
+
+		(MoreDebuggingDetail == true) ifTrue:[
+		    nm := (((ObjectMemory addressOf:con) printStringRadix:16) , ' ' , con printString).
+		] ifFalse:[
+		    nm := con printString.
+		].
+		text add:nm.
+		count := count + 1.
+	    ].
+
+	    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
+	    ].
+
+	    "/ with dense backtrace, skip the doIt methods context
+	    "/ (its dummy anyway) and fake that contexts name
+
+	    verboseBacktrace ~~ true ifTrue:[
+		(con isBlockContext
+		 and:[(h := con home) == con sender
+		 and:[((h selector == #doIt)
+		       or:[h selector == #doIt:])
+		 and:[h method who isNil]]]) ifTrue:[
+		    con := con sender.
+		    text removeLast.
+		    text add:(con methodHome printString)
+		].
+		h := nil.  "/ never keep refs to contexts unless you really need them ...
+	    ].
+
+	    "/ and also, all lazy loading intermediates
+
+	    verboseBacktrace ~~ true ifTrue:[
+		(con selector == #noByteCode 
+		and:[con receiver isMethod]) ifTrue:[
+		    contextArray removeLast.    
+		    text removeLast.
+		    con := con sender.
+		    count := count - 1.
+		]
+	    ].
+
+	    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
+	    ].
+
+	    verboseBacktrace ~~ true ifTrue:[
+		"/ in dense mode, remove the process startup
+		"/ contexts (if any)
+
+		(con := contextArray last) methodClass == Process ifTrue:[
+		    con selector == #start ifTrue:[
+			contextArray removeLast.
+			text removeLast.
+
+			[contextArray size > 0
+			 and:[contextArray last methodHome == con]] whileTrue:[
+			    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.
+	receiverInspector release.
+	contextInspector release.
     ].
 
     m notNil ifTrue:[
-        m disable:#removeBreakpoint.
-        m disable:#implementors.
-        m disable:#senders.
-        m disable:#browseClass.
+	m disable:#removeBreakpoint.
+	m disable:#implementors.
+	m disable:#senders.
+	m disable:#browseClass.
     ].
     ^ true
 
@@ -2801,10 +2801,10 @@
 
     con := aContext.
     (con notNil and:[con selector == #threadSwitch:]) ifTrue:[
-        con := con sender.
-        (con notNil and:[con selector == #timerInterrupt]) ifTrue:[
-            con := con sender.
-        ].
+	con := con sender.
+	(con notNil and:[con selector == #timerInterrupt]) ifTrue:[
+	    con := con sender.
+	].
     ].
 
     ^ self setContext:con releaseInspectors:true
@@ -2850,38 +2850,38 @@
     mClass := aContext methodClass.
 
     sel == #withCursor:do: ifTrue:[
-        (mClass == WindowGroup) ifTrue:[^ false].
-        (mClass == TopView) ifTrue:[^ false].
+	(mClass == WindowGroup) ifTrue:[^ false].
+	(mClass == TopView) ifTrue:[^ false].
     ].
     (sel == #withExecuteCursorDo:
     or:[sel == #withWaitCursorDo:]) ifTrue:[
-        (mClass == DisplaySurface) ifTrue:[^ false].
+	(mClass == DisplaySurface) ifTrue:[^ false].
     ].
 
     (mClass == Object) ifTrue:[
-        (sel startsWith:'perform:') ifTrue:[^ false]
+	(sel startsWith:'perform:') ifTrue:[^ false]
     ].
 
     (mClass == Method) ifTrue:[
-        (sel startsWith:'valueWithReceiver:') ifTrue:[^ false]
+	(sel startsWith:'valueWithReceiver:') ifTrue:[^ false]
     ].
 
     (mClass == SmallInteger) ifTrue:[
-        (sel == #to:do:) ifTrue:[^ false].
-        (sel == #to:by:do:) ifTrue:[^ false].
+	(sel == #to:do:) ifTrue:[^ false].
+	(sel == #to:by:do:) ifTrue:[^ false].
     ].
 
     (mClass == Block) ifTrue:[
-        sel == #valueNowOrOnUnwindDo: ifTrue:[^ false].
-        sel == #valueOnUnwindDo: ifTrue:[^ false].
-
-        sel == #value ifTrue:[^ false].
-        sel == #value: ifTrue:[^ false].
-        sel == #value:value: ifTrue:[^ false].
-        sel == #value:value:value: ifTrue:[^ false].
-        sel == #value:value:value:value: ifTrue:[^ false].
-        sel == #value:value:value:value:Value: ifTrue:[^ false].
-        sel == #value:value:value:value:value:value: ifTrue:[^ false].
+	sel == #valueNowOrOnUnwindDo: ifTrue:[^ false].
+	sel == #valueOnUnwindDo: ifTrue:[^ false].
+
+	sel == #value ifTrue:[^ false].
+	sel == #value: ifTrue:[^ false].
+	sel == #value:value: ifTrue:[^ false].
+	sel == #value:value:value: ifTrue:[^ false].
+	sel == #value:value:value:value: ifTrue:[^ false].
+	sel == #value:value:value:value:Value: ifTrue:[^ false].
+	sel == #value:value:value:value:value:value: ifTrue:[^ false].
     ].
 
 "/    aContext isBlockContext ifTrue:[
@@ -2898,13 +2898,13 @@
     or:[(mClass == QuerySignal)
     or:[mClass == SignalSet]]
     ) ifTrue:[
-        sel == #handle:do: ifTrue:[^ false].
+	sel == #handle:do: ifTrue:[^ false].
     ].
 
     ^ true.
 
-    "Created: 10.1.1997 / 21:01:39 / cg"
-    "Modified: 14.1.1997 / 13:25:13 / cg"
+    "Created: / 10.1.1997 / 21:01:39 / cg"
+    "Modified: / 4.1.1998 / 21:20:20 / cg"
 !
 
 stepping 
@@ -2924,24 +2924,24 @@
     |oldContext idx|
 
     inspectedProcess state == #dead ifTrue:[
-        self showTerminated.
-        ^ self
+	self showTerminated.
+	^ self
     ].
 
     oldContext := selectedContext.
     [
-        (self setContextSkippingInterruptContexts:inspectedProcess suspendedContext) ifTrue:[
-            oldContext notNil ifTrue:[
-                contextArray notNil ifTrue:[
-                    idx := contextArray identityIndexOf:oldContext.
-                    idx ~~ 0 ifTrue:[
-                        self showSelection:idx
-                    ] ifFalse:[
-                        codeView contents:('** context returned **')
-                    ]
-                ]
-            ]
-        ].
+	(self setContextSkippingInterruptContexts:inspectedProcess suspendedContext) ifTrue:[
+	    oldContext notNil ifTrue:[
+		contextArray notNil ifTrue:[
+		    idx := contextArray identityIndexOf:oldContext.
+		    idx ~~ 0 ifTrue:[
+			self showSelection:idx
+		    ] ifFalse:[
+			codeView contents:('** context returned **')
+		    ]
+		]
+	    ]
+	].
     ] valueUninterruptably.
 
     "Modified: 20.10.1996 / 18:11:24 / cg"
@@ -2958,7 +2958,7 @@
      Otherwise, the GC will not be able to release it."
 
     windowGroup notNil ifTrue:[
-        windowGroup setProcess:nil.
+	windowGroup setProcess:nil.
     ].
 
     self releaseDebuggee.
@@ -2969,11 +2969,11 @@
     "/ only cache if I am on the Display
     "/
     device == Display ifTrue:[
-        exclusive ifTrue:[
-            CachedExclusive := self
-        ] ifFalse:[
-            CachedDebugger := self
-        ].
+	exclusive ifTrue:[
+	    CachedExclusive := self
+	] ifFalse:[
+	    CachedDebugger := self
+	].
     ]
 
     "Modified: 10.7.1997 / 15:50:46 / stefan"
@@ -2984,10 +2984,10 @@
     "tell wether we are a cached debugger"
 
     CachedExclusive == self ifTrue:[
-        ^ true.
+	^ true.
     ].
     CachedDebugger == self ifTrue:[
-        ^ true.
+	^ true.
     ].
 
     ^ false.
@@ -3029,16 +3029,16 @@
     cachable := false.
 
     CachedExclusive == self ifTrue:[
-        CachedExclusive := nil.
+	CachedExclusive := nil.
     ].
     CachedDebugger == self ifTrue:[
-        CachedDebugger := nil.
+	CachedDebugger := nil.
     ].
     OpenDebuggers notNil ifTrue:[
-        idx := OpenDebuggers identityIndexOf:self.
-        idx ~~ 0 ifTrue:[
-            OpenDebuggers at:idx put:nil
-        ].
+	idx := OpenDebuggers identityIndexOf:self.
+	idx ~~ 0 ifTrue:[
+	    OpenDebuggers at:idx put:nil
+	].
     ].
 
     "Modified: 31.7.1997 / 21:20:11 / cg"
@@ -3048,18 +3048,18 @@
 
 controlLoop
     "this is a kludge:
-        start a dispatchloop which exits when
-        either continue, return or step is pressed
+	start a dispatchloop which exits when
+	either continue, return or step is pressed
     "
 
     haveControl := true.
     [
-        [haveControl] whileTrue:[
-            self controlLoopCatchingErrors
-        ].
+	[haveControl] whileTrue:[
+	    self controlLoopCatchingErrors
+	].
     ] valueNowOrOnUnwindDo:[
-        catchBlock := nil.
-        haveControl := false
+	catchBlock := nil.
+	haveControl := false
     ].
 
     "Modified: 9.7.1996 / 18:29:09 / cg"
@@ -3073,21 +3073,21 @@
     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:
+	"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 , '
@@ -3098,53 +3098,53 @@
 >>>> Message: ' , ex errorString , '
 
 caught & 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.
+	    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.
-
-            DebuggingDebugger ~~ true ifTrue:[
-                "/
-                "/ ignore recursive breakpoints
-                "/
-                (MessageTracer notNil
+	"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.
+
+	    DebuggingDebugger ~~ true ifTrue:[
+		"/
+		"/ ignore recursive breakpoints
+		"/
+		(MessageTracer notNil
 		and:[MessageTracer isLoaded
 		and:[signal == MessageTracer breakpointSignal]]) ifTrue:[
-                    'DebugView [info]: breakpoint in debugger ignored' infoPrintCR.
-                    ex proceed
-                ].
-                (signal == ActivityNotificationSignal) ifTrue:[
-                    ex proceed
-                ].
-                signal == Exception recursiveExceptionSignal ifTrue:[
+		    'DebugView [info]: breakpoint in debugger ignored' infoPrintCR.
+		    ex proceed
+		].
+		(signal == ActivityNotificationSignal) ifTrue:[
+		    ex proceed
+		].
+		signal == Exception recursiveExceptionSignal ifTrue:[
 		    (MessageTracer notNil
 		    and:[MessageTracer isLoaded
 		    and:[ex parameter signal == MessageTracer breakpointSignal]])
 		    ifTrue:[
-                        'DebugView [info]: recursive breakpoint in debugger ignored' infoPrintCR.
-                        ex proceed.
-                    ].
-
-                    self showError:'*** Recursive error in debugger:
+			'DebugView [info]: recursive breakpoint in debugger ignored' infoPrintCR.
+			ex proceed.
+		    ].
+
+		    self showError:'*** Recursive error in debugger:
 
 >>>> Signal:  ' , ex signal printString , '
 >>>>          ' , ex parameter signal printString , '
@@ -3156,29 +3156,29 @@
 >>>> Message: ' , ex errorString , '
 
 caught & ignored.'.
-                    ex return
-                ].
-            ].
-
-            self topView raiseDeiconified.    
-
-            answer := Dialog 
-                        choose:('error in debugger: ' , ex errorString , '\\debug again ?') withCRs
-                        labels:#( 'proceed' 'cancel' 'debug' ) 
-                        values:#( #proceed #cancel #debug ) 
-                        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:[]
-        ].
+		    ex return
+		].
+	    ].
+
+	    self topView raiseDeiconified.    
+
+	    answer := Dialog 
+			choose:('error in debugger: ' , ex errorString , '\\debug again ?') withCRs
+			labels:#( 'proceed' 'cancel' 'debug' ) 
+			values:#( #proceed #cancel #debug ) 
+			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.
 
@@ -3212,10 +3212,10 @@
     con := selectedContext.
     top := con.
     [con notNil] whileTrue:[
-        (con methodHome == selectedContext) ifTrue:[
-            top := con
-        ].
-        con := con sender
+	(con methodHome == selectedContext) ifTrue:[
+	    top := con
+	].
+	con := con sender
     ].
     "
      use class&selector to find the method for the compilation
@@ -3233,28 +3233,28 @@
     Class nameSpaceQuerySignal
     answer:(implementorClass nameSpace)
     do:[
-        newMethod := implementorClass compilerClass
-                             compile:someCode
-                             forClass:implementorClass
-                             inCategory:(method category)
-                             notifying:codeView.
+	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
-        ].
+	"
+	 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
 
@@ -3266,35 +3266,35 @@
 
     contextView middleButtonMenu hide.
     inspecting ifFalse:[
-        "I am running on top of a process, abort or continue it"
-
-        windowGroup notNil ifTrue:[
-            windowGroup setProcess:nil.
-        ].
-        self uncacheMyself.
-
-        "/
-        "/ catch invalid return;
-        "/ this happens, when my process has somehow died (quickterminate)
-        "/ and I am a leftOver view, which gets terminated via the launchers
-        "/ #destroy-window function.
-        "/
-        Context invalidReturnSignal handle:[:ex |
-            'DebugView [info]: OOPS - non regular debugView closing(1)' infoPrintCR.
-            self uncacheMyself.
-            Debugger newDebugger.
-            ex return.
-        ] do:[
-            canAbort ifTrue:[
-                self doAbort.
-            ] ifFalse:[
-                self doContinue
-            ]
-        ].
-        "/ We don't reach this point normally
-        'DebugView [info]: OOPS - non regular debugView closing(2)' infoPrintCR.
-        Debugger newDebugger.
-        self uncacheMyself.
+	"I am running on top of a process, abort or continue it"
+
+	windowGroup notNil ifTrue:[
+	    windowGroup setProcess:nil.
+	].
+	self uncacheMyself.
+
+	"/
+	"/ catch invalid return;
+	"/ this happens, when my process has somehow died (quickterminate)
+	"/ and I am a leftOver view, which gets terminated via the launchers
+	"/ #destroy-window function.
+	"/
+	Context invalidReturnSignal handle:[:ex |
+	    'DebugView [info]: OOPS - non regular debugView closing(1)' infoPrintCR.
+	    self uncacheMyself.
+	    Debugger newDebugger.
+	    ex return.
+	] do:[
+	    canAbort ifTrue:[
+		self doAbort.
+	    ] ifFalse:[
+		self doContinue
+	    ]
+	].
+	"/ We don't reach this point normally
+	'DebugView [info]: OOPS - non regular debugView closing(2)' infoPrintCR.
+	Debugger newDebugger.
+	self uncacheMyself.
     ].
 
 
@@ -3313,15 +3313,15 @@
     |breakPointSignal|
 
     (MessageTracer notNil and:[MessageTracer isLoaded]) ifTrue:[
-        breakPointSignal := MessageTracer breakpointSignal.
+	breakPointSignal := MessageTracer breakpointSignal.
     ].
     breakPointSignal notNil ifTrue:[
-        breakPointSignal handle:[:ex |
-            'DebugView [info]: breakpoint in debugger ignored' infoPrintCR.
-            ex proceed
-        ] do:[
+	breakPointSignal handle:[:ex |
+	    'DebugView [info]: breakpoint in debugger ignored' infoPrintCR.
+	    ex proceed
+	] do:[
 	    self updateForContext:lineNr
-        ].
+	].
     ] ifFalse:[
 	self updateForContext:lineNr
     ]
@@ -3332,30 +3332,30 @@
      Also sent to autoselect an interesting context on entry."
 
     Object errorSignal handle:[:ex |
-        |s con|
-
-        'DebugView [info]: error when showing selection in debugger ignored' infoPrintCR.
-
-        s := '' writeStream.
-        s nextPutLine:'**** error in debugger, while extracting source'.
-        s nextPutLine:'****'.
-        s nextPutAll: '**** '; nextPutLine:(ex errorString withCRs).
-        s nextPutLine:'****'.
-        con := ex suspendedContext.
-        s nextPutAll: '**** '; nextPutLine:(con printString , ' [' , con lineNumber printString , ']').
-        con := con sender.
-        [con notNil] whileTrue:[
-            s nextPutAll: '**** '; nextPutLine:(con printString , ' [' , con lineNumber printString , ']').
-            con receiver == self ifTrue:[
-                con := nil
-            ] ifFalse:[
-                con := con sender.
-            ]
-        ].
-        codeView contents:(s contents).
-        ex return.
+	|s con|
+
+	'DebugView [info]: error when showing selection in debugger ignored' infoPrintCR.
+
+	s := '' writeStream.
+	s nextPutLine:'**** error in debugger, while extracting source'.
+	s nextPutLine:'****'.
+	s nextPutAll: '**** '; nextPutLine:(ex errorString withCRs).
+	s nextPutLine:'****'.
+	con := ex suspendedContext.
+	s nextPutAll: '**** '; nextPutLine:(con printString , ' [' , con lineNumber printString , ']').
+	con := con sender.
+	[con notNil] whileTrue:[
+	    s nextPutAll: '**** '; nextPutLine:(con printString , ' [' , con lineNumber printString , ']').
+	    con receiver == self ifTrue:[
+		con := nil
+	    ] ifFalse:[
+		con := con sender.
+	    ]
+	].
+	codeView contents:(s contents).
+	ex return.
     ] do:[
-        self doShowSelection:lineNr
+	self doShowSelection:lineNr
     ]
 
     "Modified: / 8.11.1997 / 19:38:03 / cg"
@@ -3371,266 +3371,266 @@
      mthd cls codeSet|
 
     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:[
-                codeView contents:nil.
-                ^ self
-            ].
-        ].
-
-        selectedContext := con.
-        m := contextView middleButtonMenu.
-        (m notNil and:[selectedContext notNil]) ifTrue:[
-            m enableAll:#(implementors senders inspectContext)
-        ].
-
-        self withWaitCursorDo:[
-            codeSet := false.
-
-            "
-             give it to the (lower right) inspector
-            "
-            contextInspector inspect:con.
-
-            "/ show a stack inspector sometimes
-
-            con hasStackToShow ifTrue:[
-                stackInspector isNil ifTrue:[
-                    receiverInspector origin:(0.0 @ 0.0) corner:0.3 @ 1.0.
-                    contextInspector origin:(0.3 @ 0.0) corner:(0.6 @ 1.0).
-
-                    stackInspector := InspectorView
-                                        origin:(0.6 @ 0.0) corner:(1.0 @ 1.0)
-                                        in:contextInspector superView.
-                    stackInspector realize.
-                    stackInspector label:'stack'.
-                    stackInspector hideReceiver:true.
-                ].
-                stackInspector inspect:(con stackFrame asArray).
-                stackInspector showLast.
-            ] ifFalse:[
-                stackInspector notNil ifTrue:[
-                    stackInspector destroy.
-                    stackInspector := nil.
-                    receiverInspector origin:(0.0 @ 0.0) corner:0.5 @ 1.0.
-                    contextInspector origin:(0.5 @ 0.0) corner:(1.0 @ 1.0).
-                ]
-            ].
-
-            "
-             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:[
-                        Object errorSignal handle:[:ex |
-                            code := 'error while asking method for its source'.
-                            canAccept := false.
-                            ex return.
-                        ] do:[
-                            "
-                             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 := homeContext sender) notNil
-                            and:[(sender selector startsWith:'valueWithReceiver:')
-                            and:[sender receiver isMethod]]) ifTrue:[
-                                method := sender receiver.
-                                self sensor shiftDown ifTrue:[
-                                    code := method decompiledSource
-                                ] ifFalse:[
-                                    code := method source.
-                                ].
-                                canAccept := false.
-                            ] ifFalse:[
-                                (method := con method) notNil ifTrue:[
-                                    self sensor shiftDown ifTrue:[
-                                        code := method decompiledSource
-                                    ] ifFalse:[
-                                        code := method source.
-                                    ].
-                                    canAccept := false.
-                                ]
-                            ]
-                        ]
-                    ] ifFalse:[
-                        method := implementorClass compiledMethodAt:sel.
-                    ].
-                ]
-            ].
-
-            code isNil ifTrue:[
-                errMsg := nil.
-                method notNil ifTrue:[
-                    Object errorSignal handle:[:ex |
-                        code := 'error while asking method for its source'.
-                        canAccept := false.
-                        ex return.
-                    ] do:[
-                        self sensor shiftDown ifTrue:[
-                            code := method decompiledSource
-                        ] ifFalse:[
-                            code := method source.
-                        ].
-                    ].
-                    code isNil ifTrue:[
-                        method sourceFilename notNil ifTrue:[
-                            codeView contents:(resources 
-                                                       string:'** no sourcefile: %1 **'
-                                                       with:method sourceFilename).
-                            codeView flash.
-                            codeSet := true.
-                        ] 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.
-                   codeSet := true.
-                ]
-            ].
-
-            code isNil ifTrue:[
-                canAccept := false.
-                codeSet ifFalse:[
-                    codeView contents:nil.
-                ]
-            ] ifFalse:[
-                code ~= (codeView contents) ifTrue:[codeView contents:code].
-
-                (lineNrInMethod notNil and:[lineNrInMethod ~~ 0]) 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:[
+		codeView contents:nil.
+		^ self
+	    ].
+	].
+
+	selectedContext := con.
+	m := contextView middleButtonMenu.
+	(m notNil and:[selectedContext notNil]) ifTrue:[
+	    m enableAll:#(implementors senders inspectContext)
+	].
+
+	self withWaitCursorDo:[
+	    codeSet := false.
+
+	    "
+	     give it to the (lower right) inspector
+	    "
+	    contextInspector inspect:con.
+
+	    "/ show a stack inspector sometimes
+
+	    con hasStackToShow ifTrue:[
+		stackInspector isNil ifTrue:[
+		    receiverInspector origin:(0.0 @ 0.0) corner:0.3 @ 1.0.
+		    contextInspector origin:(0.3 @ 0.0) corner:(0.6 @ 1.0).
+
+		    stackInspector := InspectorView
+					origin:(0.6 @ 0.0) corner:(1.0 @ 1.0)
+					in:contextInspector superView.
+		    stackInspector realize.
+		    stackInspector label:'stack'.
+		    stackInspector hideReceiver:true.
+		].
+		stackInspector inspect:(con stackFrame asArray).
+		stackInspector showLast.
+	    ] ifFalse:[
+		stackInspector notNil ifTrue:[
+		    stackInspector destroy.
+		    stackInspector := nil.
+		    receiverInspector origin:(0.0 @ 0.0) corner:0.5 @ 1.0.
+		    contextInspector origin:(0.5 @ 0.0) corner:(1.0 @ 1.0).
+		]
+	    ].
+
+	    "
+	     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:[
+			Object errorSignal handle:[:ex |
+			    code := 'error while asking method for its source'.
+			    canAccept := false.
+			    ex return.
+			] do:[
+			    "
+			     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 := homeContext sender) notNil
+			    and:[(sender selector startsWith:'valueWithReceiver:')
+			    and:[sender receiver isMethod]]) ifTrue:[
+				method := sender receiver.
+				self sensor shiftDown ifTrue:[
+				    code := method decompiledSource
+				] ifFalse:[
+				    code := method source.
+				].
+				canAccept := false.
+			    ] ifFalse:[
+				(method := con method) notNil ifTrue:[
+				    self sensor shiftDown ifTrue:[
+					code := method decompiledSource
+				    ] ifFalse:[
+					code := method source.
+				    ].
+				    canAccept := false.
+				]
+			    ]
+			]
+		    ] ifFalse:[
+			method := implementorClass compiledMethodAt:sel.
+		    ].
+		]
+	    ].
+
+	    code isNil ifTrue:[
+		errMsg := nil.
+		method notNil ifTrue:[
+		    Object errorSignal handle:[:ex |
+			code := 'error while asking method for its source'.
+			canAccept := false.
+			ex return.
+		    ] do:[
+			self sensor shiftDown ifTrue:[
+			    code := method decompiledSource
+			] ifFalse:[
+			    code := method source.
+			].
+		    ].
+		    code isNil ifTrue:[
+			method sourceFilename notNil ifTrue:[
+			    codeView contents:(resources 
+						       string:'** no sourcefile: %1 **'
+						       with:method sourceFilename).
+			    codeView flash.
+			    codeSet := true.
+			] 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.
+		   codeSet := true.
+		]
+	    ].
+
+	    code isNil ifTrue:[
+		canAccept := false.
+		codeSet ifFalse:[
+		    codeView contents:nil.
+		]
+	    ] ifFalse:[
+		code ~= (codeView contents) ifTrue:[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
-                    ]
-                ].
-            ].
-
-            codeView acceptEnabled:canAccept.
-            canAccept ifTrue:[
-                codeView acceptAction:[:code | self codeAccept:code asString]
-            ] ifFalse:[
-                codeView acceptAction:[:code | self device beep].
-            ].
-
-            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
-        ].
+		    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
+		    ]
+		].
+	    ].
+
+	    codeView acceptEnabled:canAccept.
+	    canAccept ifTrue:[
+		codeView acceptAction:[:code | self codeAccept:code asString]
+	    ] ifFalse:[
+		codeView acceptAction:[:code | self device beep].
+	    ].
+
+	    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
+	].
     ] ifFalse:[
-        codeView contents:nil.
+	codeView contents:nil.
     ].
 
     con isContext ifFalse:[
-        sendButton disable.
+	sendButton disable.
     ] ifTrue:[
-        sendButton enable.
+	sendButton enable.
     ].
 
     "clear out locals to prevent keeping around unneeded contexts 
@@ -3646,24 +3646,24 @@
     "
     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:[
-            cls := mthd containingClass.
-        ].
-        m enable:#browseClass.
-        cls notNil ifTrue:[
-            m enableAll:#(browse browseClass browseClassHierarchy browseFullClassProtocol).
-        ] ifFalse:[
-            m disableAll:#(browse browseClass browseClassHierarchy browseFullClassProtocol).
-        ].
+	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:[
+	    cls := mthd containingClass.
+	].
+	m enable:#browseClass.
+	cls notNil ifTrue:[
+	    m enableAll:#(browse browseClass browseClassHierarchy browseFullClassProtocol).
+	] ifFalse:[
+	    m disableAll:#(browse browseClass browseClassHierarchy browseFullClassProtocol).
+	].
     ]
 
     "Created: 14.8.1997 / 20:15:00 / cg"
@@ -3673,6 +3673,6 @@
 !DebugView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libtool/DebugView.st,v 1.180 1997-11-11 15:01:40 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/DebugView.st,v 1.181 1998-01-05 13:05:15 cg Exp $'
 ! !
 DebugView initialize!