[ENH]Automatic Transcript Openning

Noury Bouraqadi bouraqadi at ensm-douai.fr
Wed Oct 22 08:45:58 UTC 2003


Hi,

I was tired of openning transcript manually in every new project.
So,I made this short hack to ensure that there is always at least one 
Transcript view open in every project. Its very usefull to have the 
transcript open. One can see what's going on. Especially when fileIn 
code since potential problems (undeclared stuff) are displayed on the 
transcript.

I think that we must go a step further and provide a little framework to 
allow users setup in preference which windows should be opened in every 
browser... May be someone already did it. In this case, please tell me.

Regards,
Noury

-- 
------------------------------------------
Dr. Noury Bouraqadi - Enseignant/Chercheur
Ecole des Mines de Douai - Dept. G.I.P
http://csl.ensm-douai.fr/noury

European Smalltalk Users Group
http://www.esug.org 

Squeak: an Open Source Smalltalk
http://www.squeak.org 
------------------------------------------

-------------- next part --------------
'From Squeak3.7alpha of ''11 September 2003'' [latest update: #5423] on 22 October 2003 at 9:12:03 am'!
"Change Set:		ProjectWithTranscript
Date:			22 October 2003
Author:			Noury Bouraqadi

Forces having at least one Transcript open in each project"!


!Project methodsFor: 'menu messages'!
enter: returningFlag revert: revertFlag saveForRevert: saveForRevert
	"Install my ChangeSet, Transcript, and scheduled views as current globals. If returningFlag is true, we will return to the project from whence the current project was entered; don't change its previousProject link in this case.
	If saveForRevert is true, save the ImageSegment of the project being left.
	If revertFlag is true, make stubs for the world of the project being left.
	If revertWithoutAsking is true in the project being left, then always revert."

	| showZoom recorderOrNil old forceRevert response seg newProcess |

	(world isKindOf: StringMorph) ifTrue: [
		self inform: 'This project is not all here. I will try to load a complete version.'.
		^self loadFromServer: true	"try to get a fresh copy"
	].
	self isCurrentProject ifTrue: [^ self].
	"Check the guards"
	guards ifNotNil:
		[guards _ guards reject: [:obj | obj isNil].
		guards do: [:obj | obj okayToEnterProject ifFalse: [^ self]]].
	CurrentProject world triggerEvent: #aboutToLeaveWorld.
	forceRevert _ false.
	CurrentProject rawParameters 
		ifNil: [revertFlag ifTrue: [^ self inform: 'nothing to revert to']]
		ifNotNil: [saveForRevert ifFalse: [
				forceRevert _ CurrentProject projectParameters 
								at: #revertWithoutAsking ifAbsent: [false]]].
	forceRevert not & revertFlag ifTrue: [
		response _ SelectionMenu confirm: 'Are you sure you want to destroy this Project\ and revert to an older version?\\(From the parent project, click on this project''s thumbnail.)' withCRs
			trueChoice: 'Revert to saved version' 
			falseChoice: 'Cancel'.
		response ifFalse: [^ self]].

	revertFlag | forceRevert 
		ifTrue: [seg _ CurrentProject projectParameters at: #revertToMe ifAbsent: [
					^ self inform: 'nothing to revert to']]
		ifFalse: [
			CurrentProject finalExitActions.
			CurrentProject makeThumbnail.
			returningFlag == #specialReturn
				ifTrue:
					[ProjectHistory forget: CurrentProject.		"this guy is irrelevant"
					Project forget: CurrentProject]
				ifFalse:
					[ProjectHistory remember: CurrentProject]].

	(revertFlag | saveForRevert | forceRevert) ifFalse:
		[(Preferences valueOfFlag: #projectsSentToDisk) ifTrue:
			[self storeToMakeRoom]].

	CurrentProject abortResourceLoading.
	Smalltalk isMorphic ifTrue: [CurrentProject world triggerClosingScripts].

	CurrentProject saveProjectPreferences.

	"Update the display depth and make a thumbnail of the current project"
	CurrentProject displayDepth: Display depth.
	old _ CurrentProject.		"for later"

	"Show the project transition.
	Note: The project zoom is run in the context of the old project,
		so that eventual errors can be handled accordingly"
	displayDepth == nil ifTrue: [displayDepth _ Display depth].
	self installNewDisplay: Display extent depth: displayDepth.
	(showZoom _ self showZoom) ifTrue: [
		self displayZoom: CurrentProject parent ~~ self].

	(world isMorph and: [world hasProperty: #letTheMusicPlay])
		ifTrue: [world removeProperty: #letTheMusicPlay]
		ifFalse: [Smalltalk at: #ScorePlayer ifPresentAndInMemory:
					[:playerClass | playerClass allSubInstancesDo:
						[:player | player pause]]].

	returningFlag == #specialReturn ifTrue: [
		old removeChangeSetIfPossible.	"keep this stuff from accumulating"
		nextProject _ nil
	] ifFalse: [
		returningFlag
			ifTrue: [nextProject _ CurrentProject]
			ifFalse: [previousProject _ CurrentProject].
	].

	CurrentProject saveState.
	CurrentProject isolationHead == self isolationHead ifFalse:
		[self invokeFrom: CurrentProject].
	CurrentProject _ self.
	self installProjectPreferences.
	ChangeSet  newChanges: changeSet.
	TranscriptStream newTranscript: transcript.
	Sensor flushKeyboard.
	Smalltalk isMorphic ifTrue: [recorderOrNil _ World pauseEventRecorder].

	ProjectHistory remember: CurrentProject.

	world isMorph
		ifTrue:
			[World _ world.  "Signifies Morphic"
			world install.
			world transferRemoteServerFrom: old world.
			"(revertFlag | saveForRevert | forceRevert) ifFalse: [
				(Preferences valueOfFlag: #projectsSentToDisk) ifTrue: [
					self storeSomeSegment]]."
			recorderOrNil ifNotNil: [recorderOrNil resumeIn: world].
			world triggerOpeningScripts]
		ifFalse:
			[World _ nil.  "Signifies MVC"
			Smalltalk at: #ScheduledControllers put: world].

	saveForRevert ifTrue: [
		Smalltalk garbageCollect.	"let go of pointers"
		old storeSegment.
		"result _" old world isInMemory 
			ifTrue: ['Can''t seem to write the project.']
			ifFalse: [old projectParameters at: #revertToMe put: 
					old world xxxSegment clone].
				'Project written.'].
			"original is for coming back in and continuing."

	revertFlag | forceRevert ifTrue: [
		seg clone revert].	"non-cloned one is for reverting again later"
	self removeParameter: #exportState.

	Transcript openCount = 0 ifTrue: [Transcript open].
	"Complete the enter: by launching a new process"
	world isMorph ifTrue: [
		self finalEnterActions.
		world repairEmbeddedWorlds.
		world triggerEvent: #aboutToEnterWorld.
		Project spawnNewProcessAndTerminateOld: true
	] ifFalse: [
		SystemWindow clearTopWindow.	"break external ref to this project"
		newProcess _ [	
			ScheduledControllers resetActiveController.	"in case of walkback in #restore"
			showZoom ifFalse: [ScheduledControllers restore].
			ScheduledControllers searchForActiveController
		] fixTemps newProcess priority: Processor userSchedulingPriority.
		newProcess resume.		"lose the current process and its referenced morphs"
		Processor terminateActive.
	]! !


!TranscriptStream methodsFor: 'initialization' stamp: 'Noury Bouraqadi 10/22/2003 09:07'!
openCount
	^self dependents 
		inject: 0 
		into: [:openCount :dependent | 
				((dependent isKindOf: PluggableTextView) or:
					[dependent isKindOf: PluggableTextMorph]) 
						ifTrue: [openCount + 1]
						ifFalse: [openCount]]! !



More information about the Squeak-dev mailing list