[squeak-dev] Emergency Projects (was: The Inbox: Morphic-dtl.1376.mcz)

David T. Lewis lewis at mail.msen.com
Wed Dec 13 03:42:54 UTC 2017


On Mon, Dec 11, 2017 at 08:38:51AM -0500, David T. Lewis wrote:
> I think that it wlll work with the most recent versions of Morphic-dtl.1376,
> ST80-dtl.233, and System-dtl.983 in the inbox.
> 
> I'll check it later tonight to make sure.

Unfortunately I am not able to test the sound service, because I do not
have sound output on the cog/spur VMs on my Linux computer. Maybe someone
else can double check to make sure that #letTheMusicPlay still works. I
think I have it right, but I can't verify it on my PC.

I am attaching a change set with the lastest version of the changes, which
may be more convenient that loading the MCZs from the inbox.

Dave



> 
> I moved the "SoundService stop" from Project>>finalExitActions: to
> MVCProject>>finalExitActions: so that it would not affect Morphic, which
> handles it differently (and the Morphic handling would not work for MVC
> or SqueakShellProject).
> 
> I'm not sure if SoundService is important in a SqueakShellProject, but
> if so, it would be necessary to add the "SoundService stop" to
> SqueakShellProject>>finalExitActions:.
> 
> So maybe it would be better to leave the SoundService handling as it was?
> In that case we could add handling for EmergencyRecoveryRequested in
> MorphicProject>>finalExitActions:. But overall I think I prefer calling
> super in the that method, although I cannot really give any good reason
> for preferring it.
> 
> Thanks for looking that this :-)
> 
> Thanks,
> Dave 
> 
> On Mon, Dec 11, 2017 at 07:48:25AM +0100, Marcel Taeumel wrote:
> > Hmm... now #letTheMusicPlay cannot work anymore. :-)
> > 
> > Best,
> > Marcel
> > Am 10.12.2017 20:07:19 schrieb commits at source.squeak.org <commits at source.squeak.org>:
> > David T. Lewis uploaded a new version of Morphic to project The Inbox:
> > http://source.squeak.org/inbox/Morphic-dtl.1376.mcz
> > 
> > ==================== Summary ====================
> > 
> > Name: Morphic-dtl.1376
> > Author: dtl
> > Time: 10 December 2017, 2:04:07.58309 pm
> > UUID: eaa7809b-73bf-4643-b2a1-3d9d7ac54362
> > Ancestors: Morphic-nice.1375
> > 
> > Call super in finalExitActions: in order to clear the EmergencyRecoveryRequested guard.
> > 
> > =============== Diff against Morphic-nice.1375 ===============
> > 
> > Item was changed:
> > ----- Method: MorphicProject>>finalExitActions: (in category 'enter') -----
> > finalExitActions: enteringProject
> > 
> > + super finalExitActions: enteringProject.
> > world triggerClosingScripts.
> > -
> > "Pause sound players, subject to preference settings"
> > (world hasProperty: #letTheMusicPlay)
> > ifTrue: [world removeProperty: #letTheMusicPlay]
> > ifFalse: [SoundService stop].
> > 
> > world sleep.
> > (world findA: ProjectNavigationMorph)
> > ifNotNil: [:navigator | navigator retractIfAppropriate].
> > self clearGlobalState.
> > Sensor flushAllButDandDEvents. !
> > 
> > 
> 
> > 
-------------- next part --------------
'From Squeak6.0alpha of 7 December 2017 [latest update: #17574] on 12 December 2017 at 10:21:11 pm'!
"Change Set:		EmergencyProjects-dtl
Date:			12 December 2017
Author:			David T Lewis

When an emergency evaluator is required, first search parent projects for a suitable project in which to host the debugger. Then search all projects, looking for any project of different kind.

When opening a project for emergency recovery, let the debugger window title identify the project from which the emergency condition originated.

Prevent infinite recursion by providing a guard flag to indicate that a project has already requested an emergency evaluator. If an attempt is made to open another project for emergency evaluation while the guard is active, fall back on the tradition emergency evaluator transcript instead."!

Model subclass: #Project
	instanceVariableNames: 'world uiManager changeSet transcript parentProject previousProject displayDepth viewSize thumbnail nextProject projectParameters version urlList lastDirectory lastSavedAtSeconds projectPreferenceFlagDictionary resourceManager emergencyRecoveryRequested '
	classVariableNames: 'AllProjects CurrentProject GoalFreePercent GoalNotMoreThan EmergencyRecoveryRequested '
	poolDictionaries: ''
	category: 'System-Support'!
Project class
	instanceVariableNames: ''!

!Project methodsFor: 'enter' stamp: 'dtl 12/9/2017 10:35'!
finalExitActions: enteringProject

	EmergencyRecoveryRequested := false. "clear fence variable if previously set due to error"
! !

!Project methodsFor: 'enter - recovery' stamp: 'dtl 12/9/2017 10:35'!
enterForEmergencyRecovery
	"Stripped down verion of #enter:revert:saveForRevert:. More error handling. Less features."
	
	| leavingProject process titleForDebuggerWindow |
	self isCurrentProject ifTrue: [^ self].
	EmergencyRecoveryRequested == true ifTrue: [^ self].
	EmergencyRecoveryRequested := true.

	titleForDebuggerWindow := 'FATAL PROJECT ERROR: Project was ''', CurrentProject name, ''''.
	ProjectHistory remember: CurrentProject.
	nextProject := CurrentProject.
	
	[ CurrentProject world triggerEvent: #aboutToLeaveWorld.
	CurrentProject abortResourceLoading.
	CurrentProject finalExitActions: self.
	CurrentProject saveState ] on: Error do: [:ex | "Ignore." ].
	
	"********** SWITCHING CURRENT PROJECT **********"
	leavingProject := CurrentProject.
	CurrentProject := self.
	ProjectHistory remember: self.
	"********** SWITCHING CURRENT PROJECT **********"

	self loadState.
	self finalEnterActions: leavingProject.
	self addDeferredUIMessage: [self startResourceLoading].
	self world triggerEvent: #aboutToEnterWorld.
	
	"Now that everything is set up, we can show zoom animation.
	Do we really need this in case of an emergency?"
	self showZoom
		ifTrue: [self displayZoom: leavingProject parent ~~ self "Entering?"]
		ifFalse: [self restore].
	
	"Update processes at last."
	self scheduleProcessForEnter.
	
	"Do not terminate but suspend the projects ui process to support debugging."
	process := leavingProject uiProcess.
	self addDeferredUIMessage: [process debugWithTitle: titleForDebuggerWindow].
	leavingProject suspendProcessForDebug.! !


!MVCProject methodsFor: 'enter' stamp: 'dtl 12/8/2017 00:14'!
finalExitActions: enteringProject

	super finalExitActions: enteringProject.
	SoundService stop.

	self world unCacheWindows.
	Sensor flushAllButDandDEvents.
	
	ScheduledControllers := nil.! !


!MorphicProject methodsFor: 'enter' stamp: 'dtl 12/8/2017 00:15'!
finalExitActions: enteringProject

	super finalExitActions: enteringProject.
	world triggerClosingScripts.
	"Pause sound players, subject to preference settings"
	(world hasProperty: #letTheMusicPlay)
		ifTrue: [world removeProperty: #letTheMusicPlay]
		ifFalse: [SoundService stop].

	world sleep.
	(world findA: ProjectNavigationMorph)
		ifNotNil: [:navigator | navigator retractIfAppropriate].
	self clearGlobalState.
	Sensor flushAllButDandDEvents. ! !


!Project class methodsFor: 'error recovery' stamp: 'dtl 12/11/2017 21:13'!
tryOtherProjectForRecovery: errorMessage
	"Try entering the parent project if it uses a different user interface. We determine this by comparing the project's class."
	
	| safeProject nextProject |
	nextProject := Project current.
	safeProject := nil.
	"Search parent projects for one of a different type"
	[safeProject notNil or: [nextProject isTopProject]] whileFalse: [
		nextProject := nextProject parent.
		(Project current isKindOf: nextProject class)
			ifFalse: [safeProject := nextProject]].
	"No suitable parent project found, search all projects for any one of different type."
	safeProject ifNil: [Smalltalk garbageCollect.
		safeProject := Project allSubInstances
			detect: [:proj | (proj isKindOf: Project current class) not] ifNone: []].
	safeProject ifNotNil: [:p | 
		p enterForEmergencyRecovery.
		"Active process will usually suspend after this."].
! !


!Project class reorganize!
('class initialization' cleanUp: initialize localeChanged rebuildAllProjects)
('constants' current uiManager uiProcess)
('squeaklet on server' enterIfThereOrFind: fromUrl: isBadNameForStoring: loaderUrl mostRecent:onServer: namedUrl: parseProjectFileName: projectExtension serverDirectoryFromURL: serverFileFromURL: squeakletDirectory sweep:)
('dispatching' baseSelectors dispatchSelectors isDispatchSelector:)
('utilities' addingProject: advanceToNextProject allNames allNamesAndProjects allProjects allProjectsOrdered canWeLoadAProjectNow chooseNaturalLanguage deletingProject: enter: flattenProjectHierarchy forget: hierarchyOfNamesAndProjects jumpToProject jumpToSelection: maybeForkInterrupt named: named:in: namedWithDepth: ofWorld: projectHierarchy releaseProjectReferences: removeAll: removeAllButCurrent resumeProcess: returnToParentProject returnToPreviousProject storeAllInSegments topProject versionForFileName:)
('deprecated')
('*Morphic-Support' allMorphicProjects)
('*51Deprecated' interruptName: spawnNewProcess spawnNewProcessAndTerminateOld: spawnNewProcessIfThisIsUI:)
('error recovery' handlePrimitiveError: tryEmergencyEvaluatorForRecovery: tryOtherProjectForRecovery:)
('shrinking' removeProjectsFromSystem)
('snapshots' shutDown: startUp:)
('*ST80-Support' allMVCProjects)
('preferences' publishInSexp)
('*Etoys-Squeakland-instance creation' enterNew enterNewWithInitialBalloons)
('*Etoys-Squeakland-squeaklet on server' fromExampleEtoys:)
('*Etoys-Squeakland-constants' home)
('*Etoys-Squeakland-utilities' cleanUpEtoysGarbage interruptName:preemptedProcess: makeANewLocalGallery)
!

Model subclass: #Project
	instanceVariableNames: 'world uiManager changeSet transcript parentProject previousProject displayDepth viewSize thumbnail nextProject projectParameters version urlList lastDirectory lastSavedAtSeconds projectPreferenceFlagDictionary resourceManager'
	classVariableNames: 'AllProjects CurrentProject EmergencyRecoveryRequested GoalFreePercent GoalNotMoreThan'
	poolDictionaries: ''
	category: 'System-Support'!


More information about the Squeak-dev mailing list