[squeak-dev] The Trunk: System-ul.324.mcz

commits at source.squeak.org commits at source.squeak.org
Sun May 2 11:02:34 UTC 2010


Levente Uzonyi uploaded a new version of System to project The Trunk:
http://source.squeak.org/trunk/System-ul.324.mcz

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

Name: System-ul.324
Author: ul
Time: 2 May 2010, 12:20:57.034 pm
UUID: 0c7bb02d-416f-9d47-ae30-8b9c9cdc9c72
Ancestors: System-bf.323

- rehash all HashedCollections not just Sets

=============== Diff against System-bf.323 ===============

Item was changed:
  ----- Method: ImageSegment>>restoreEndianness (in category 'fileIn/Out') -----
  restoreEndianness
  	"Fix endianness (byte order) of any objects not already fixed.  Do this by discovering classes that need a startUp message sent to each instance, and sending it.
  	I have just been brought in and converted to live objects.  Find all Sets and Dictionaries in the newly created objects and rehash them.  Segment is near then end of memory, since is was newly brought in (and a new object created for it).
  	Also, collect all classes of receivers of blocks which refer to instance variables.  Return them.  Caller will check if they have been reshaped."
  
+ 	| object hashedCollections receiverClasses inSeg noStartUpNeeded startUps cls msg |
- 	| object sets receiverClasses inSeg noStartUpNeeded startUps cls msg |
  
  	object := segment.
+ 	hashedCollections := OrderedCollection new.
- 	sets := OrderedCollection new.
  		"have to collect them, because Dictionary makes a copy, and that winds up at the end of memory and gets rehashed and makes another one."
  	receiverClasses := IdentitySet new.
  	noStartUpNeeded := IdentitySet new.	"classes that don't have a per-instance startUp message"
  	startUps := IdentityDictionary new.	"class -> MessageSend of a startUp message"
  	inSeg := true.
  	[object := object nextObject.  "all the way to the end of memory to catch remade objects"
  		object == endMarker ifTrue: [inSeg := false].	"off end"
  		object isInMemory ifTrue: [
+ 			(object isKindOf: HashedCollection) ifTrue: [hashedCollections add: object].
- 			(object isKindOf: Set) ifTrue: [sets add: object].
  			(object isKindOf: ContextPart) ifTrue: [
  				(inSeg and: [object hasInstVarRef]) ifTrue: [
  					receiverClasses add: object receiver class]].
  			inSeg ifTrue: [
  				(noStartUpNeeded includes: object class) ifFalse: [
  					cls := object class.
  					(msg := startUps at: cls ifAbsent: [nil]) ifNil: [
  						msg := cls startUpFrom: self.	"a Message, if we need to swap bytes this time"
  						msg ifNil: [noStartUpNeeded add: cls]
  							ifNotNil: [startUps at: cls put: msg]].
  					msg ifNotNil: [msg sentTo: object]]]]. 
  		object == 0] whileFalse.
+ 	hashedCollections do: #rehash.	"our purpose"
- 	sets do: [:each | each rehash].	"our purpose"
  	^ receiverClasses	"our secondary job"
  !

Item was changed:
  ----- Method: ProjectLoading class>>openName:stream:fromDirectory:withProjectView: (in category 'loading') -----
  openName: aFileName stream: preStream fromDirectory: aDirectoryOrNil
  withProjectView: existingView
  	"Reconstitute a Morph from the selected file, presumed to be
  represent a Morph saved via the SmartRefStream mechanism, and open it
  in an appropriate Morphic world."
  
     	| morphOrList proj trusted localDir projStream archive mgr
  projectsToBeDeleted baseChangeSet enterRestricted substituteFont
  numberOfFontSubstitutes exceptions |
  	(preStream isNil or: [preStream size = 0]) ifTrue: [
  		ProgressNotification  signal: '9999 about to enter
  project'.		"the hard part is over"
  		^self inform:
  'It looks like a problem occurred while
  getting this project. It may be temporary,
  so you may want to try again,' translated
  	].
  	ProgressNotification signal: '2:fileSizeDetermined
  ',preStream size printString.
  	preStream isZipArchive
  		ifTrue:[	archive := ZipArchive new readFrom: preStream.
  				projStream := self
  projectStreamFromArchive: archive]
  		ifFalse:[projStream := preStream].
  	trusted := SecurityManager default positionToSecureContentsOf:
  projStream.
  	trusted ifFalse:
  		[enterRestricted := (preStream isTypeHTTP or:
  [aFileName isNil])
  			ifTrue: [Preferences securityChecksEnabled]
  			ifFalse: [Preferences standaloneSecurityChecksEnabled].
  		enterRestricted
  			ifTrue: [SecurityManager default enterRestrictedMode
  				ifFalse:
  					[preStream close.
  					^ self]]].
  
  	localDir := Project squeakletDirectory.
  	aFileName ifNotNil: [
  		(aDirectoryOrNil isNil or: [aDirectoryOrNil pathName
  ~= localDir pathName]) ifTrue: [
  			localDir deleteFileNamed: aFileName.
  			(localDir fileNamed: aFileName) binary
  				nextPutAll: preStream contents;
  				close.
  		].
  	].
  	morphOrList := projStream asUnZippedStream.
  	preStream sleep.		"if ftp, let the connection close"
  	ProgressNotification  signal: '3:unzipped'.
  	ResourceCollector current: ResourceCollector new.
  	baseChangeSet := ChangeSet current.
  	self useTempChangeSet.		"named zzTemp"
  	"The actual reading happens here"
  	substituteFont := Preferences standardEToysFont copy.
  	numberOfFontSubstitutes := 0.
  	exceptions := Set new.
  	[[morphOrList := morphOrList fileInObjectAndCodeForProject]
  		on: FontSubstitutionDuringLoading do: [ :ex |
  				exceptions add: ex.
  				numberOfFontSubstitutes :=
  numberOfFontSubstitutes + 1.
  				ex resume: substituteFont ]]
  			ensure: [ ChangeSet  newChanges: baseChangeSet].
  	mgr := ResourceManager new initializeFrom: ResourceCollector current.
  	mgr fixJISX0208Resource.
  	mgr registerUnloadedResources.
  	archive ifNotNil:[mgr preLoadFromArchive: archive cacheName:
  aFileName].
  	(preStream respondsTo: #close) ifTrue:[preStream close].
  	ResourceCollector current: nil.
  	ProgressNotification  signal: '4:filedIn'.
  	ProgressNotification  signal: '9999 about to enter project'.
  		"the hard part is over"
  	(morphOrList isKindOf: ImageSegment) ifTrue: [
  		proj := morphOrList arrayOfRoots
  			detect: [:mm | mm isKindOf: Project]
  			ifNone: [^self inform: 'No project found in
  this file'].
  		proj projectParameters at: #substitutedFont put: (
  			numberOfFontSubstitutes > 0
  				ifTrue: [substituteFont]
  				ifFalse: [#none]).
  		proj projectParameters at: #MultiSymbolInWrongPlace put: false.
  			"Yoshiki did not put MultiSymbols into
  outPointers in older images!!"
  		morphOrList arrayOfRoots do: [:obj |
  			obj fixUponLoad: proj seg: morphOrList "imageSegment"].
  		(proj projectParameters at: #MultiSymbolInWrongPlace) ifTrue: [
  			morphOrList arrayOfRoots do: [:obj | (obj
+ isKindOf: HashedCollection) ifTrue: [obj rehash]]].
- isKindOf: Set) ifTrue: [obj rehash]]].
  
  		proj resourceManager: mgr.
  		"proj versionFrom: preStream."
  		proj lastDirectory: aDirectoryOrNil.
  		proj setParent: Project current.
  		projectsToBeDeleted := OrderedCollection new.
  		existingView ifNil: [
  			ChangeSet allChangeSets add: proj changeSet.
  			Project current openProject: proj.
  				"Note: in MVC we get no further than the above"
  		] ifNotNil: [
  			(existingView project isKindOf: DiskProxy) ifFalse: [
  				existingView project changeSet name: 
  ChangeSet defaultName.
  				projectsToBeDeleted add: existingView project.
  			].
  			(existingView owner isSystemWindow) ifTrue: [
  				existingView owner model: proj
  			].
  			existingView project: proj.
  		].
  		ChangeSet allChangeSets add: proj changeSet.
  		Project current projectParameters
  			at: #deleteWhenEnteringNewProject
  			ifPresent: [ :ignored |
  				projectsToBeDeleted add: Project current.
  				Project current removeParameter:
  #deleteWhenEnteringNewProject.
  			].
  		projectsToBeDeleted isEmpty ifFalse: [
  			proj projectParameters
  				at: #projectsToBeDeleted
  				put: projectsToBeDeleted.
  		].
  		^ ProjectEntryNotification signal: proj
  	].
  	Project current openViewAndEnter: morphOrList
  !

Item was changed:
  ----- Method: ImageSegment>>rehashSets (in category 'fileIn/Out') -----
  rehashSets
  	"I have just been brought in and converted to live objects.  Find all Sets and Dictionaries in the newly created objects and rehash them.  Segment is near then end of memory, since is was newly brought in (and a new object created for it).
  	Also, collect all classes of receivers of blocks.  Return them.  Caller will check if they have been reshaped."
  
+ 	| object hashedCollections receiverClasses inSeg |
- 	| object sets receiverClasses inSeg |
  	object := segment.
+ 	hashedCollections := OrderedCollection new.
- 	sets := OrderedCollection new.
  		"have to collect them, because Dictionary makes a copy, and that winds up at the end of memory and gets rehashed and makes another one."
  	receiverClasses := IdentitySet new.
  	inSeg := true.
  	[object := object nextObject.  
  		object == endMarker ifTrue: [inSeg := false].	"off end"
  		object isInMemory ifTrue: [
+ 			(object isKindOf: HashedCollection) ifTrue: [hashedCollections add: object].
- 			(object isKindOf: Set) ifTrue: [sets add: object].
  			object isBlock ifTrue: [inSeg ifTrue: [
  					receiverClasses add: object receiver class]].	
  			object class == MethodContext ifTrue: [inSeg ifTrue: [
  					receiverClasses add: object receiver class]].	
  			]. 
  		object == 0] whileFalse.
+ 	hashedCollections do: #rehash. "our purpose"
- 	sets do: [:each | each rehash].	"our purpose"
  	^ receiverClasses	"our secondary job"
  !




More information about the Squeak-dev mailing list