[squeak-dev] The Trunk: System-ar.165.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Nov 12 09:20:17 UTC 2009


Andreas Raab uploaded a new version of System to project The Trunk:
http://source.squeak.org/trunk/System-ar.165.mcz

==================== Summary ====================

Name: System-ar.165
Author: ar
Time: 12 November 2009, 1:19:41 am
UUID: 14583ce0-5a9e-a94b-ac87-f0608bc2025a
Ancestors: System-dtl.164

Remove support for isolation layers.

=============== Diff against System-dtl.164 ===============

Item was changed:
  ----- Method: Project>>enter:revert:saveForRevert: (in category 'enter') -----
  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 |
  
  	self isIncompletelyLoaded ifTrue:
  		[^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' translated]]
  		ifNotNil: [saveForRevert ifFalse: [
  				forceRevert := CurrentProject projectParameters 
  								at: #revertWithoutAsking ifAbsent: [false]]].
  	forceRevert not & revertFlag ifTrue: [
  		response := (UIManager default chooseFrom: {
  			'Revert to saved version' translated.
  			'Cancel' translated.
  		} title: '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.)' translated withCRs) = 1.
  		response ifFalse: [^ self]].
  
  	revertFlag | forceRevert 
  		ifTrue: [seg := CurrentProject projectParameters at: #revertToMe ifAbsent: [
  					^ self inform: 'nothing to revert to' translated]]
  		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.
  	CurrentProject 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].
  
  	CurrentProject pauseSoundPlayers.
  
  	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.
  	recorderOrNil := old pauseEventRecorder.
  	ProjectHistory remember: CurrentProject.
  	self setWorldForEnterFrom: old recorder: recorderOrNil.
  
  	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.
  
  	"Complete the enter: by launching a new process"
  	self scheduleProcessForEnter: showZoom
  !

Item was changed:
  ----- Method: Project>>setChangeSet: (in category 'initialization') -----
  setChangeSet: aChangeSet
  
- 	isolatedHead == true ifTrue: [^ self].  "ChangeSet of an isolated project cannot be changed"
  	changeSet := aChangeSet
  !

Item was changed:
  Model subclass: #Project
+ 	instanceVariableNames: 'world changeSet transcript parentProject previousProject displayDepth viewSize thumbnail nextProject guards projectParameters version urlList environment lastDirectory lastSavedAtSeconds projectPreferenceFlagDictionary resourceManager'
- 	instanceVariableNames: 'world changeSet transcript parentProject previousProject displayDepth viewSize thumbnail nextProject guards projectParameters isolatedHead inForce version urlList environment lastDirectory lastSavedAtSeconds projectPreferenceFlagDictionary resourceManager'
  	classVariableNames: 'AllProjects CurrentProject GoalFreePercent GoalNotMoreThan UIProcess'
  	poolDictionaries: ''
  	category: 'System-Support'!
  
  !Project commentStamp: 'tk 12/2/2004 12:38' prior: 0!
  A Project stores the state of a complete Squeak desktop, including
  the windows, and the currently active changeSet.  A project knows who
  its parent project is.  When you change projects, whether by entering
  or exiting, the screen state of the project being exited is saved in
  that project.
  
  A project is retained by its view in the parent world.  It is
  effectively named by the name of its changeSet, which can be changed
  either by renaming in a changeSorter, or by editing the label of its
  view from the parent project.
  
  As the site of major context switch, Projects are the locus of
  swapping between the old MVC and the new Morphic worlds.  The
  distinction is based on whether the variable 'world' contains a
  WorldMorph or a ControlManager.
  
  Saving and Loading
  Projects may be stored on the disk in external format.  (Project
  named: 'xxx') exportSegment, or choose 'store project on file...'.
  Projects may be loaded from a server and stored back.  Storing on a
  server never overwrites;  it always makes a new version.  A project
  remembers the url of where it lives in urlList.  The list is length
  one, for now.  The url may point to a local disk instead of a server.
  All projects that the user looks at, are cached in the Squeaklet
  folder.  Sorted by server.  The cache holds the most recent version
  only.
  
  When a project is loaded into Squeak, its objects are converted to
  the current version.  There are three levels of conversion.  First,
  each object is converted from raw bits to an object in its old
  format.  Then it is sent some or all of these messages:
  	comeFullyUpOnReload: smartRefStream  		Used to
  re-discover an object that already exists in this image, such as a
  resource, global variable, Character, or Symbol.  (sent to objects in
  outPointers)
  	convertToCurrentVersion: varDict refStream: smartRefStrm
  		fill in fields that have been added to a class since
  the object was stored.  Used to set the extra inst var to a default
  value.  Or, return a new object of a different class.  (sent to
  objects that changed instance variables)
  	fixUponLoad: aProject refStream: smartRefStrm
  	change the object due to conventions that have changed on the
  project level.  (sent to all objects in the incoming project)
  
  Here is the calling sequence for storing out a Project:
  Project saveAs
  Project storeOnServer
  Project storeOnServerWithProgressInfo
  Project storeOnServerInnards
  Project exportSegmentFileName:directory:
  Project exportSegmentWithChangeSet:fileName:directory:
  ImageSegment writeForExportWithSources:inDirectory:changeSet:
  ---------
  Isolation (not used any more)
  When you accept a method, the entire system feels the change, except
  projects that are "isolated".  In an isolated project, all new global
  variables (including new classes) arestored in the project-local
  environment, and all changes to preexisting classes are revoked when
  you leave the project.  When you enter another project, that
  project's changes are invoked.  Invocation and revocation are handled
  efficiently by swapping pointers.  To make a project be isolated,
  choose 'isolate changes of this project' from the 'changes...'
  section of the screen menu.  You can use an isolated project for
  making dangerous change to a system, and you can get out if it
  crashes.  A foreign application can have the separate environment it
  wants.  Also, you can freeze part of the system for a demo that you
  don't want to disturb.  An isolated project shares methods with all
  subprojects inside it, unless they are isolated themselves.   Each
  isolated project is the head of a tree of projects with which it
  shares all methods.
  
  You may 'assert' all changes ever made in the current project to take
  effect above this project.  This amounts to exporting all the globals
  in the current environment, and zapping the revocation lists to that
  the current state of the world will remain in force upon exit from
  this project.
  
  [Later: A project may be 'frozen'.  Asserts do not apply to it after
  that.  (Great for demos.)  You should be informed when an assert was
  blocked in a frozen project.]
  
  Class definitions are layered by the isolation mechanism.  You are
  only allowed to change the shape of a class in projects that lie
  within its isolation scope.  All versions of the methods are
  recompiled, in all projects.  If you remove an inst var that is in
  use in an isolated project, it will become an Undeclared global.  It
  is best not to remove an inst var when it is being used in another
  isolated project. [If we recompile them all, why can't we diagnose
  the problem before allowing the change??]
  
  Senders and Implementors do not see versions of a method in isolated
  projects.  [again, we might want to make this possible at a cost].
  When you ask for versions of a method, you will not get the history
  in other isolated projects.
  
  Moving methods and classes between changeSets, and merging changeSets
  has no effect on which methods are in force.  But, when you look at a
  changeSet from a different isolated project, the methods will contain
  code that is not in force.  A changeSet is just a list of method
  names, and does not keep separate copies of any code.
  
  When finer grained assertion is needed, use the method (aProject
  assertClass: aClass from: thisProject warn: warnConflicts).
  
  How isolated changes work: The first time a class changes, store its
  MethodDictionary object.  Keep parallel arrays of associations to
  Classes and MethodDictionaries.  Traverse these and install them when
  you enter an "ioslated project".  When you leave, store this
  project's own MethodDictionaries there.
  	To do an assert, we must discover which methods changed here,
  and which changed only in the project we are asserting into.  There
  is one copy of the 'virgin' method dictionaries in the system.  It is
  always being temporarily stored by the currently inForce isolated
  project.
  
  isolatedHead - true for the top project, and for each isolated
  project.  false or nil for any subproject that shares all methods
  with its parent project.
  
  inForce -  true if my methods are installed now.  false if I am
  dormant. [is this equivalent to self == Project Current?]
  
  classArray - list of associations to classes
  
  methodDictArray - the method dictionaries of those classes before we
  started changing methods.  They hang onto the original
  compiledMethods.  (If this project is dormant, it contains the method
  dictionaries of those classes as they will be here, in this project).
  
  orgArray - the class organizations of the classes in classArray.
  
  UsingIsolation (class variable) - No longer used.
  
  When you want to save a project in export format from within that
  very project, it gets tricky.  We set two flags in parentProject,
  exit to it, and let parentProject write the project.
  ProjectViewMorph in parentProject checks in its step method, does the
  store, clears the flags, and reenters the subProject.
  
  !

Item was changed:
  ----- Method: ChangeSet class>>newChanges: (in category 'current changeset') -----
  newChanges: aChangeSet 
  	"Set the system ChangeSet to be the argument, aChangeSet.  Tell the current project that aChangeSet is now its change set.  When called from Project enter:, the setChangeSet: call is redundant but harmless; when called from code that changes the current-change-set from within a project, it's vital"
  
  	SystemChangeNotifier uniqueInstance noMoreNotificationsFor: current.
- 	current isolationSet: nil.
  	current := aChangeSet.
  	SystemChangeNotifier uniqueInstance notify: aChangeSet ofAllSystemChangesUsing: #event:.
+ 	Smalltalk currentProjectDo:[:proj |
+ 		proj setChangeSet: aChangeSet]!
- 	Smalltalk currentProjectDo:
- 		[:proj |
- 		proj setChangeSet: aChangeSet.
- 		aChangeSet isolationSet: proj isolationSet]!

Item was changed:
  ----- Method: Project>>initialize (in category 'initialization') -----
  initialize
  	"Initialize the project, seting the CurrentProject as my parentProject and initializing my project preferences from those of the CurrentProject"
  	Project addingProject: self.
  	changeSet := ChangeSet new.
  	transcript := TranscriptStream new.
  	displayDepth := Display depth.
  	parentProject := CurrentProject.
- 	isolatedHead := false.
  	self initializeProjectPreferences
  !

Item was removed:
- ----- Method: Project>>isolationHead (in category 'isolation layers') -----
- isolationHead
- 	"Go up the parent chain and find the nearest isolated project."
- 
- 	isolatedHead == true ifTrue: [^ self].
- 	self isTopProject ifTrue: [^ nil].
- 	^ parentProject isolationHead!

Item was removed:
- ----- Method: Project>>compileAll:from: (in category 'isolation layers') -----
- compileAll: newClass from: oldClass
- 	"Make sure that shadowed methods in isolation layers get recompiled.
- 	Traversal is done elsewhere.  This simply handles the current project."
- 
- 	isolatedHead == true ifFalse: [^ self].   "only isolated projects need to act on this."
- 	
- 	changeSet compileAll: newClass from: oldClass!

Item was removed:
- ----- Method: Project>>invoke (in category 'isolation layers') -----
- invoke
- 	"Install all methods changed here into method dictionaries.
- 	Make my versions be the ones that will be called."
- 
- 	isolatedHead ifFalse: [^ self error: 'This isnt an isolation layer.'].
- 	inForce ifTrue: [^ self error: 'This layer is already in force.'].
- 	changeSet invoke.	
- 	inForce := true.!

Item was removed:
- ----- Method: Project>>propagateChanges (in category 'isolation layers') -----
- propagateChanges
- 	"Assert these changes in the next higher isolation layer of the system."
- 
- 	isolatedHead ifFalse: [self error: 'You can only assert changes from isolated projects'].
- 	self halt: 'Not Yet Implemented'.
- 
- "This will be done by installing a new changeSet for this project (initted for isolation).  With the old changeSet no longer in place, no revert will happen when we leave, and those changes will have effectively propagated up a level.  NOTE: for this to work in general, the changes here must be assimilated into the isolationSet for the next layer."!

Item was removed:
- ----- Method: Project>>layersToTop (in category 'isolation layers') -----
- layersToTop
- 	"Return an OrderedCollection of all the projects that are isolation layers from this one up to the top of the project hierarchy, inclusive."
- 
- 	| layers |
- 	self isTopProject
- 		ifTrue: [layers := OrderedCollection new]
- 		ifFalse: [layers := parentProject layersToTop].
- 	isolatedHead ifTrue: [layers addFirst: self].
- 	^ layers
- !

Item was removed:
- ----- Method: Project>>isIsolated (in category 'isolation layers') -----
- isIsolated
- 
- 	^ isolatedHead ifNil: [isolatedHead := false]!

Item was removed:
- ----- Method: ChangeSet>>compileAll:from: (in category 'isolation layers') -----
- compileAll: newClass from: oldClass
- 	"If I have changes for this class, recompile them"
- 
- 	(changeRecords at: newClass ifAbsent: [^ self])
- 		compileAll: newClass from: oldClass
- !

Item was removed:
- ----- Method: Project>>invokeFrom: (in category 'isolation layers') -----
- invokeFrom: otherProject
- 	"Revoke the changes in force for this project, and then invoke those in force for otherProject.  This method shortens the process to the shortest path up then down through the isolation layers."
- 
- 	| pathUp pathDown |
- 	pathUp := otherProject layersToTop.  "Full paths to top"
- 	pathDown := self layersToTop.
- 
- 	"Shorten paths to nearest common ancestor"
- 	[pathUp isEmpty not
- 		and: [pathDown isEmpty not
- 		and: [pathUp last == pathDown last]]]
- 		whileTrue: [pathUp removeLast.  pathDown removeLast].
- 
- 	"Now revoke changes up from otherProject and invoke down to self."
- 	pathUp do: [:p | p revoke].
- 	pathDown reverseDo: [:p | p invoke].
- !

Item was removed:
- ----- Method: Project>>convertToCurrentVersion:refStream: (in category 'object fileIn') -----
- convertToCurrentVersion: varDict refStream: smartRefStrm
- 	
- 	isolatedHead ifNil: [isolatedHead := false].
- 	inForce ifNil: [inForce := false].
- 	^super convertToCurrentVersion: varDict refStream: smartRefStrm.
- 
- !

Item was removed:
- ----- Method: Project>>enterForEmergencyRecovery (in category 'enter') -----
- enterForEmergencyRecovery
- 	"This version of enter invokes an absolute minimum of mechanism.
- 	An unrecoverable error has been detected in an isolated project.
- 	It is assumed that the old changeSet has already been revoked.
- 	No new process gets spawned here.  This will happen in the debugger."
- 
- 	self flag: #toRemove. "dtl Nov 2009: Per guidance from ar, this is part of an experimental
- 		project and should be removed (along with #setWorldForEmergencyRecovery).
- 		Currently there are senders that must be resolved prior to removal. Reference:
- 		http://lists.squeakfoundation.org/pipermail/squeak-dev/2009-November/140762.html"
- 
- 	self isCurrentProject ifTrue: [^ self].
- 	CurrentProject saveState.
- 	CurrentProject := self.
- 	Display newDepthNoRestore: displayDepth.
- 	ChangeSet  newChanges: changeSet.
- 	TranscriptStream newTranscript: transcript.
- 	World pauseEventRecorder.
- 	self setWorldForEmergencyRecovery.
- 	UIProcess := Processor activeProcess
- !

Item was removed:
- ----- Method: Project>>isolationSet (in category 'isolation layers') -----
- isolationSet
- 
- 	"Return the changeSet for this isolation layer or nil"
- 	isolatedHead == true ifTrue: [^ changeSet].
- 	self isTopProject ifTrue: [^ nil].  "At the top, but not isolated"
- 	^ parentProject isolationSet
- 
- !

Item was removed:
- ----- Method: Project>>revoke (in category 'isolation layers') -----
- revoke
- 	"Take back all methods changed here.
- 	Install the original method dictionaries and organizations.
- 	The orignal method versions will now be the ones used."
- 
- 	isolatedHead ifFalse: [^ self error: 'This isnt an isolation layer.'].
- 	inForce ifFalse: [^ self error: 'This layer should have been in force.'].
- 	changeSet revoke.	
- 	inForce := false.
- !

Item was removed:
- ----- Method: Project>>compileAllIsolated:from: (in category 'isolation layers') -----
- compileAllIsolated: newClass from: oldClass
- 	"Whenever a recompile is needed in a class, look in other isolated projects for saved methods and recompile them also.
- 	At the time this method is called, the recompilation has already been done for the project now in force."
- 
- 	Project allProjects do: [:proj | proj compileAll: newClass from: oldClass].
- 
- !

Item was removed:
- ----- Method: Project>>beIsolated (in category 'isolation layers') -----
- beIsolated
- 	"Establish an isolation layer at this project.
- 	This requires clearing the current changeSet or installing a new one."
- 
- 	isolatedHead ifTrue: [^ self error: 'Already isolated'].
- 	self isCurrentProject ifFalse:
- 		[^ self inform: 'Must be in this project to isolate it'.].
- 	changeSet isEmpty ifFalse: [changeSet := ChangeSet newChangeSet].
- 	changeSet beIsolationSetFor: self.
- 	isolatedHead := true.
- 	inForce := true.!




More information about the Squeak-dev mailing list