[squeak-dev] The Trunk: System-eem.142.mcz

commits at source.squeak.org commits at source.squeak.org
Sun Sep 6 05:15:23 UTC 2009


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

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

Name: System-eem.142
Author: eem
Time: 5 September 2009, 5:14:21 am
UUID: ae7696f5-b413-4aa6-8255-f41ed57953f2
Ancestors: System-ar.141

Seventh package of eight in closure compiler fixes 9/5/2009.

use new temp names encoding scheme in abandonSources and exportCodeSegment:classes:keepSource:

Use correct compiler class when parsing the selectors of ChangeRecords.

Move some block-local temps into blocks in Change scanning

=============== Diff against System-ar.141 ===============

Item was changed:
  ----- Method: ClassChangeRecord>>compileAll:from: (in category 'method changes') -----
  compileAll: newClass from: oldClass
  	"Something about this class has changed.  Locally retained methods must be recompiled.
  	NOTE:  You might think that if this changeSet is in force, then we can just note
  	the new methods but a lower change set may override and be in force which
  	would mean that only the overriding copies go recompiled.  Just do it."
  
- 	| sel changeType changeRecord newMethod |
  	methodChanges associationsDo:
+ 		[:assn | | sel changeType changeRecord newMethod |
+ 		sel := assn key.
+ 		changeRecord := assn value.
- 		[:assn | sel := assn key.  changeRecord := assn value.
  		changeType := changeRecord changeType.
  		(changeType == #add or: [changeType == #change]) ifTrue:
  			[newMethod := newClass
  				recompileNonResidentMethod: changeRecord currentMethod
  				atSelector: sel from: oldClass.
  			changeRecord noteNewMethod: newMethod]]!

Item was changed:
  ----- Method: ChangeRecord>>methodSelector (in category 'access') -----
  methodSelector
+ 	^type == #method ifTrue:
+ 		[(Smalltalk at: class ifAbsent: [Object]) parserClass new parseSelector: self string]!
- 	type == #method
- 		ifFalse: [^ nil].
- 	^ self class parserClass new parseSelector: self string!

Item was changed:
  ----- Method: CodeLoader class>>exportCodeSegment:classes:keepSource: (in category 'utilities') -----
  exportCodeSegment: exportName classes: aClassList keepSource: keepSources
  
  	"Code for writing out a specific category of classes as an external image segment.  Perhaps this should be a method."
  
+ 	| is oldMethods newMethods classList symbolHolder fileName |
- 	| is oldMethods newMethods m oldCodeString argsAndTemps classList symbolHolder fileName |
  	keepSources
  		ifTrue: [
  			self confirm: 'We are going to abandon sources.
  Quit without saving after this has run.' orCancel: [^self]].
  
  	classList := aClassList asArray.
  
  	"Strong pointers to symbols"
  	symbolHolder := Symbol allInstances.
  
  	oldMethods := OrderedCollection new: classList size * 150.
  	newMethods := OrderedCollection new: classList size * 150.
  	keepSources
  		ifTrue: [
  			classList do: [:cl |
  				cl selectors do:
+ 					[:selector | | m oldCodeString methodNode |
- 					[:selector |
  					m := cl compiledMethodAt: selector.
  					m fileIndex > 0 ifTrue:
  						[oldCodeString := cl sourceCodeAt: selector.
+ 						methodNode := cl compilerClass new
+ 											parse: oldCodeString in: cl notifying: nil.
- 						argsAndTemps := (cl compilerClass new
- 							parse: oldCodeString in: cl notifying: nil) tempNames.
  						oldMethods addLast: m.
+ 						newMethods addLast: (m copyWithTempsFromMethodNode: methodNode)]]]].
- 						newMethods addLast: (m copyWithTempNames: argsAndTemps)]]]].
  	oldMethods asArray elementsExchangeIdentityWith: newMethods asArray.
+ 	oldMethods := newMethods := nil.
- 	oldMethods := newMethods := m := oldCodeString := argsAndTemps := nil.
  
  	Smalltalk garbageCollect.
  	is := ImageSegment new copyFromRootsForExport: classList.	"Classes and MetaClasses"
  
  	fileName := FileDirectory fileName: exportName extension: ImageSegment fileExtension.
  	is writeForExport: fileName.
  	self compressFileNamed: fileName
  
  !

Item was changed:
  ----- Method: ClassChangeRecord>>methodChangeTypes (in category 'method changes') -----
  methodChangeTypes
  	"Return an old-style dictionary of method change types."
  
+ 	| dict |
- 	| dict selector record |
  	dict := IdentityDictionary new.
  	methodChanges associationsDo:
+ 		[:assn | | selector record |
+ 		selector := assn key.
+ 		record := assn value.
- 		[:assn | selector := assn key.  record := assn value.
  		dict at: selector put: record changeType].
  	^ dict!

Item was changed:
  ----- Method: ClassChangeRecord>>forgetChangesIn: (in category 'removal') -----
  forgetChangesIn: otherRecord
  	"See forgetAllChangesFoundIn:.  Used in culling changeSets."
  
+ 	| cls otherMethodChanges |
- 	| cls otherMethodChanges selector actionToSubtract |
  	(cls := self realClass) == nil ifTrue: [^ self].  "We can do better now, though..."
  	otherMethodChanges := otherRecord methodChangeTypes.
  	otherMethodChanges associationsDo:
+ 		[:assoc | | selector actionToSubtract |
+ 		selector := assoc key. actionToSubtract := assoc value.
- 		[:assoc | selector := assoc key. actionToSubtract := assoc value.
  		(cls includesSelector: selector)
  			ifTrue: [(#(add change) includes: actionToSubtract)
  					ifTrue: [methodChanges removeKey: selector ifAbsent: []]]
  			ifFalse: [(#(remove addedThenRemoved) includes: actionToSubtract)
  					ifTrue: [methodChanges removeKey: selector ifAbsent: []]]].
  	changeTypes isEmpty ifFalse:
  		[changeTypes removeAllFoundIn: otherRecord allChangeTypes.
  		(changeTypes includes: #rename) ifFalse:
  			[changeTypes removeAllSuchThat: [:x | x beginsWith: 'oldName: ']]]!

Item was changed:
  ----- Method: SystemDictionary>>abandonSources (in category 'shrinking') -----
  abandonSources
  	"Smalltalk abandonSources"
+ 	"Replaces every method by a copy with the 4-byte source pointer 
+ 	 replaced by a string of all arg and temp names, followed by its
+ 	 length. These names can then be used to inform the decompiler."
- 	"Replaces every method by a copy with the 4-byte source
- 	pointer 
- 	replaced by a string of all arg and temp names, followed by its
- 	length. These names can then be used to inform the
- 	decompiler. See stats below"
  	"wod 11/3/1998: zap the organization before rather than after
+ 	 condensing changes."
+ 	"eem 7/1/2009 13:59 update for the closure schematic temp names regime"
+ 	| oldMethods newMethods bTotal bCount |
- 	condensing changes."
- 	| oldCodeString argsAndTemps oldMethods newMethods m bTotal bCount |
  	(self confirm: 'This method will preserve most temp names
+ (up to about 15k characters of temporaries)
+ while allowing the sources file to be discarded.
- (up to about 400 characters) while allowing
- the sources file to be discarded.
  -- CAUTION --
  If you have backed up your system and
  are prepared to face the consequences of
  abandoning source code files, choose Yes.
  If you have any doubts, you may choose No
  to back out with no harm done.')
  			== true
  		ifFalse: [^ self inform: 'Okay - no harm done'].
  	self forgetDoIts.
  	oldMethods := OrderedCollection new: CompiledMethod instanceCount.
  	newMethods := OrderedCollection new: CompiledMethod instanceCount.
  	bTotal := 0.
  	bCount := 0.
+ 	self systemNavigation allBehaviorsDo: [:b | bTotal := bTotal + 1].
- 	self systemNavigation
- 		allBehaviorsDo: [:b | bTotal := bTotal + 1].
  	'Saving temp names for better decompilation...'
  		displayProgressAt: Sensor cursorPoint
  		from: 0
  		to: bTotal
+ 		during:
+ 			[:bar |
+ 			self systemNavigation allBehaviorsDo:
+ 				[:cl |  "for test: (Array with: Arc with: Arc class) do:"
+ 				bar value: (bCount := bCount + 1).
+ 				cl selectors do:
+ 					[:selector | | m oldCodeString methodNode |
+ 					m := cl compiledMethodAt: selector.
+ 					m fileIndex > 0 ifTrue:
+ 						[oldCodeString := cl sourceCodeAt: selector.
+ 						methodNode := cl compilerClass new
+ 											parse: oldCodeString
+ 											in: cl
+ 											notifying: nil.
+ 						oldMethods addLast: m.
+ 						newMethods addLast: (m copyWithTempsFromMethodNode: methodNode)]]]].
- 		during: [:bar | self systemNavigation
- 				allBehaviorsDo: [:cl | 
- 					"for test: (Array with: Arc with: Arc class) do:"
- 					bar value: (bCount := bCount + 1).
- 					cl selectors
- 						do: [:selector | 
- 							m := cl compiledMethodAt: selector.
- 							m fileIndex > 0
- 								ifTrue: [oldCodeString := cl sourceCodeAt: selector.
- 									argsAndTemps := (cl compilerClass new
- 												parse: oldCodeString
- 												in: cl
- 												notifying: nil) tempNames.
- 									oldMethods addLast: m.
- 									newMethods
- 										addLast: (m copyWithTempNames: argsAndTemps)]]]].
  	oldMethods asArray elementsExchangeIdentityWith: newMethods asArray.
+ 	self systemNavigation allBehaviorsDo: [:b | b zapOrganization].
- 	self systemNavigation
- 		allBehaviorsDo: [:b | b zapOrganization].
  	self condenseChanges.
  	Preferences disable: #warnIfNoSourcesFile!

Item was changed:
  ----- Method: ClassChangeRecord>>invokePhase1 (in category 'isolation layers') -----
  invokePhase1
  
+ 	| elements |
- 	| selector changeRecord type elements |
  	revertable ifFalse: [^ self].
  	inForce ifTrue: [self error: 'Can invoke only when not in force.'].
  
  	"Do the first part of the invoke operation -- no particular hurry."
  	"Save the outer method dictionary for quick revert of method changes."
  	priorMD := self realClass methodDict.
  
  	"Prepare a methodDictionary for switcheroo."
  	thisMD := self realClass methodDict copy.
  	methodChanges associationsDo:
+ 		[:assn | | selector changeRecord type |
+ 		selector := assn key.
+ 		changeRecord := assn value.
- 		[:assn | selector := assn key. changeRecord := assn value.
  		type := changeRecord changeType.
  		type = #remove ifTrue: [thisMD removeKey: selector].
  		type = #add ifTrue: [thisMD at: selector put: changeRecord currentMethod].
  		type = #change ifTrue: [thisMD at: selector put: changeRecord currentMethod].
  		].
  
  	"Replace the original organization (and comment)."
  	priorOrganization := self realClass organization.
  	thisOrganization elementArray copy do:
  		[:sel | (thisMD includesKey: sel) ifFalse: [thisOrganization removeElement: sel]].
  	#(DoIt DoItIn:) do: [:sel | thisMD removeKey: sel ifAbsent: []].
  	thisOrganization elementArray size = thisMD size ifFalse:
  		[elements := thisOrganization elementArray asSet.
  		thisMD keysDo:
  			[:sel | (elements includes: sel) ifFalse:
  				[thisOrganization classify: sel
  					under: (priorOrganization categoryOfElement: sel)]]].
  	self realClass organization: thisOrganization.
  
  
  !




More information about the Squeak-dev mailing list