[squeak-dev] Re: MVC debugging

Florin Mateoc fmateoc at gmail.com
Sat Sep 11 05:43:50 UTC 2010


 On 9/11/2010 1:42 AM, Florin Mateoc wrote:
>  On 9/10/2010 9:33 PM, Florin Mateoc wrote:
>>  On 9/10/2010 7:48 AM, David T. Lewis wrote:
>>> I think that your changes are pretty non-controversial, certainly open1... is not a good selector :)
>>>
>>> But I would have hoped that the community would play a little with these changes before they get cleaned up and
>>> integrated (Hopefully that's what Andreas is doing ;) )
>>> There are many possible scenarios (multiple projects, morphic and mvc combinations, switching back and forth (with the
>>> debugger up) - I did get some walkback when switching back to morphic but did not investigate - , hitting errors during
>>> debugging, debugging with no windows (screen only) versus with windows, exceptions from ui and from non-ui).
>>> Well, we still have some work to do to get ControlManager>>interruptName:preemptedProcess:
>>> working right. Background is at http://bugs.squeak.org/view.php?id=1041
>>> but the basic idea is that all four of the following should be interruptable:
>>>
>>>    "[true] whileTrue"
>>>    "[[true] whileTrue] forkAt: Processor userSchedulingPriority + 1"
>>>    "Smalltalk createStackOverflow"
>>>    "[Smalltalk createStackOverflow] forkAt: Processor userSchedulingPriority + 1"
>>>
>>> I spent some time trying to get this working last night, but have not yet
>>> come up with a solution. The basic idea is if the low space interrupt watcher
>>> process has called #interruptName:preemptedProcess: passing it theInterruptedProcess,
>>> then we want the debugger to open on theInterruptedProcess rather than on
>>> activeControllerProcess. This is a bit tricky to debug for obvious reasons ;)
>>>
>>> Dave
>>>
>> Of course that if we pass the preempted process, we have to honor that request.
>> But I am not sure if I understand correctly. If I have a runaway non-ui process, I don't think that the user interrupt
>> should try to find it and interrupt it. I think user interrupt is and should be dedicated to the ui process. Now once
>> you open a debugger, you can have a list of currently running processes from which you can select and debug.
>>
>> Florin
>>
>>
> Ok, with the current changeset you can interrupt "[true] whileTrue" or "Smalltalk createStackOverflow", and if you let
> "Smalltalk createStackOverflow" run, it will trigger the low space watcher and you can then recover.
>
> For interrupting processes running at higher priority I think the appropriate solution is not the debugger but an
> emergency evaluator running at an even higher priority
>
> Florin
>
>

Oops, forgot the changeset
-------------- next part --------------
'From Squeak4.1 of 17 April 2010 [latest update: #9957] on 11 September 2010 at 1:35:57 am'!

!ControlManager methodsFor: 'scheduling' stamp: 'fm 9/11/2010 00:10'!
interruptName: labelString
	"Create a Notifier on the active scheduling process with the given label. Make the Notifier the active controller."

	^ self interruptName: labelString preemptedProcess: activeControllerProcess
! !

!ControlManager methodsFor: 'scheduling' stamp: 'fm 9/11/2010 01:26'!
interruptName: labelString preemptedProcess: theInterruptedProcess
	"Create a Notifier on the interrupted process with the given label. Make the Notifier the active controller."

	theInterruptedProcess suspend.

	(activeController ~~ nil and: [activeController ~~ screenController]) ifTrue: [
		theInterruptedProcess == activeControllerProcess
			ifTrue: [
				"Carefully de-emphasis the current window."
				activeController view topView deEmphasizeForDebugger]
			ifFalse: [
				activeController controlTerminate]].

	"This will just scheduleNoTerminate the newly built controller"
	Debugger
			openInterrupt: labelString
			onProcess: theInterruptedProcess.

	self searchForActiveController! !


!Debugger methodsFor: 'initialize' stamp: 'fm 9/8/2010 01:42'!
openFullNoSuspendLabel: aString
	"Create and schedule a full debugger with the given label. Do not terminate the current active process."

	| oldContextStackIndex |
	oldContextStackIndex := contextStackIndex.
	self expandStack. "Sets contextStackIndex to zero."
	ToolBuilder open1: self label: aString.
	self toggleContextStackIndex: oldContextStackIndex.! !

!Debugger methodsFor: 'initialize' stamp: 'fm 9/8/2010 15:16'!
openNotifierContents: msgString label: label
	"Create and schedule a notifier view with the given label and message. A notifier view shows just the message or the first several lines of the stack, with a menu that allows the user to open a full debugger if so desired."
	"NOTE: When this method returns, a new process has been scheduled to run the windows, and thus this notifier, but the previous active porcess has not been suspended.  The sender will do this."
	| msg builder spec |
	Sensor flushKeyboard.
	savedCursor := Sensor currentCursor.
	Sensor currentCursor: Cursor normal.
	(label beginsWith: 'Space is low')
		ifTrue: [msg := self lowSpaceChoices, (msgString ifNil: [''])]
		ifFalse: [msg := msgString].
	builder := ToolBuilder default.
	spec := self buildNotifierWith: builder label: label message: msg.
	self expandStack.
	builder open1: spec.
	errorWasInUIProcess := Project spawnNewProcessIfThisIsUI: interruptedProcess.
! !


!Debugger class methodsFor: 'opening' stamp: 'fm 9/9/2010 00:54'!
openOn: process context: context label: title contents: contentsStringOrNil fullView: bool
	"Open a notifier in response to an error, halt, or notify. A notifier view just shows a short view of the sender stack and provides a menu that lets the user open a full debugger."

	| controller errorWasInUIProcess debugger |
	Smalltalk isMorphic
		ifTrue: [errorWasInUIProcess := Project spawnNewProcessIfThisIsUI: process]
		ifFalse: [
			controller := ScheduledControllers activeControllerProcess == process
				ifTrue: [ScheduledControllers activeController].
			[
			debugger := self new process: process controller: controller context: context.
			bool
				ifTrue: [debugger openFullNoSuspendLabel: title]
				ifFalse: [debugger openNotifierContents: contentsStringOrNil label: title].
			Preferences logDebuggerStackToFile ifTrue: [
				Smalltalk logError: title inContext: context to: 'SqueakDebug.log'].
			] on: Error do: [:ex |
				self primitiveError: 
					'Orginal error: ', 
					title asString, '.
	Debugger error: ', 
				([ex description] on: Error do: ['a ', ex class printString]), ':'
			]].
	WorldState addDeferredUIMessage: [ 
		"schedule debugger in deferred UI message to address redraw
		problems after opening a debugger e.g. from the testrunner."
		[
			debugger := self new process: process controller: nil context: context.
			bool
				ifTrue: [debugger openFullNoSuspendLabel: title]
				ifFalse: [debugger openNotifierContents: contentsStringOrNil label: title].
			debugger errorWasInUIProcess: errorWasInUIProcess.
			Preferences logDebuggerStackToFile ifTrue: [
				Smalltalk logError: title inContext: context to: 'SqueakDebug.log'].
		] on: Error do: [:ex |
			self primitiveError: 
				'Orginal error: ', 
				title asString, '.
	Debugger error: ', 
				([ex description] on: Error do: ['a ', ex class printString]), ':'
		]
	].
	process suspend.
! !


!MVCToolBuilder methodsFor: 'opening' stamp: 'fm 9/8/2010 15:23'!
open1: anObject
	"Build and open the object. Answer the widget opened."
	| window |
	window := self build: anObject.
	window controller openNoTerminate.
	^window! !

!MVCToolBuilder methodsFor: 'opening' stamp: 'fm 9/8/2010 01:41'!
open1: anObject label: aString
	"Build an open the object, labeling it appropriately.  Answer the widget opened."
	| window |
	window := self build: anObject.
	window label: aString.
	window controller openNoTerminate.
	^window! !


!MorphicToolBuilder methodsFor: 'opening' stamp: 'fm 9/8/2010 01:39'!
open1: anObject
	"Build and open the object. Answer the widget opened."
	| morph |
	anObject isMorph 
		ifTrue:[morph := anObject]
		ifFalse:[morph := self build: anObject].
	(morph isKindOf: MenuMorph)
		ifTrue:[morph popUpInWorld: World].
	(morph isKindOf: SystemWindow)
		ifTrue:[morph openInWorldExtent: morph extent]
		ifFalse:[morph openInWorld].
	^morph! !

!MorphicToolBuilder methodsFor: 'opening' stamp: 'fm 9/8/2010 01:41'!
open1: anObject label: aString
	"Build an open the object, labeling it appropriately.  Answer the widget opened."
	| window |
	window := self open: anObject.
	window setLabel: aString.
	^window! !


!Project methodsFor: 'scheduling' stamp: 'fm 9/11/2010 00:56'!
interruptName: labelString
	"Create a Notifier on the active scheduling process with the given label."

	^ self subclassResponsibility
! !


!MVCProject methodsFor: 'utilities' stamp: 'fm 9/11/2010 00:55'!
interruptName: labelString
	"Create a Notifier on the active scheduling process with the given label."

	^ ScheduledControllers interruptName: labelString
! !

!MVCProject methodsFor: 'utilities' stamp: 'fm 9/11/2010 00:22'!
interruptName: labelString preemptedProcess: theInterruptedProcess
	"Create a Notifier on the active scheduling process with the given label."

	^ ScheduledControllers interruptName: labelString preemptedProcess: theInterruptedProcess
! !


!MorphicProject methodsFor: 'scheduling' stamp: 'fm 9/11/2010 00:54'!
interruptName: labelString
	"Create a Notifier on the active scheduling process with the given label."

	^ self interruptName: labelString preemptedProcess: nil! !


!Project class methodsFor: 'utilities' stamp: 'fm 9/11/2010 01:15'!
interruptName: labelString
	"Create a Notifier on the active scheduling process with the given label."

	self flag: #toRemove. "after restarting the user interrupt watcher process"
	^ self current interruptName: labelString
! !


!ToolBuilder class methodsFor: 'instance creation' stamp: 'fm 9/8/2010 02:10'!
open1: aClass label: aString
	^self default open1: aClass label: aString! !


!MVCToolBuilder class methodsFor: 'accessing' stamp: 'fm 9/8/2010 11:52'!
isActiveBuilder
	"Answer whether I am the currently active builder"
	"This is really a way of answering whether 'Smalltalk isMVC'"
	ScheduledControllers ifNil:[^false].
	^(ScheduledControllers activeControllerProcess ifNil:[^false]) isTerminated not! !



More information about the Squeak-dev mailing list