[squeak-dev] The Trunk: System-nice.428.mcz

commits at source.squeak.org commits at source.squeak.org
Wed Mar 30 20:09:40 UTC 2011


Nicolas Cellier uploaded a new version of System to project The Trunk:
http://source.squeak.org/trunk/System-nice.428.mcz

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

Name: System-nice.428
Author: nice
Time: 30 March 2011, 10:08:55.293 pm
UUID: 600c7f8a-fbc8-47eb-b06f-5a9b93a9c677
Ancestors: System-ul.427

Use #newCompiler #newParser

=============== Diff against System-ul.427 ===============

Item was changed:
  ----- Method: BreakpointManager class>>breakpointMethodSourceFor:in: (in category 'private') -----
  breakpointMethodSourceFor: aSymbol in: aClass 
  	"Compose new source containing a break statement (currently it will be the first,
  	later we want to insert it in any place)"
  
  	| oldSource methodNode breakOnlyMethodNode sendBreakMessageNode |
  	oldSource := aClass sourceCodeAt: aSymbol.
+ 	methodNode := aClass newCompiler
- 	methodNode := aClass compilerClass new
  		compile: oldSource
  		in: aClass 
  		notifying: nil 
  		ifFail: [self error: '[breakpoint] unable to install breakpoint'].
+ 	breakOnlyMethodNode := aClass newCompiler
- 	breakOnlyMethodNode := aClass compilerClass new
  		compile: 'temporaryMethodSelectorForBreakpoint
  self break.
  ^self'
  		in: aClass 
  		notifying: nil 
  		ifFail: [self error: '[breakpoint] unable to install breakpoint'].
  	sendBreakMessageNode := breakOnlyMethodNode block statements first.
  	methodNode block statements addFirst: sendBreakMessageNode.
  	^methodNode printString
  	!

Item was changed:
  ----- Method: BreakpointManager class>>compilePrototype:in: (in category 'private') -----
  compilePrototype: aSymbol in: aClass 
  	"Compile and return a new method containing a break statement"
  
  	| source node method |
  	source := self breakpointMethodSourceFor: aSymbol in: aClass.
+ 	node := aClass newCompiler
- 	node := aClass compilerClass new
  		compile: source
  		in: aClass 
  		notifying: nil 
  		ifFail: [self error: '[breakpoint] unable to install breakpoint'].
  	node isNil ifTrue: [^nil].
  	"dunno what the arguments mean..."
  	method := node generate.
  	^method!

Item was changed:
  ----- Method: ChangeRecord>>methodSelector (in category 'access') -----
  methodSelector
  	^type == #method ifTrue:
+ 		[(Smalltalk at: class ifAbsent: [Object]) newParser parseSelector: self string]!
- 		[(Smalltalk at: class ifAbsent: [Object]) 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 |
  	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 allSymbols.
  
  	oldMethods := OrderedCollection new: classList size * 150.
  	newMethods := OrderedCollection new: classList size * 150.
  	keepSources
  		ifTrue: [
  			classList do: [:cl |
  				cl selectorsAndMethodsDo:
  					[:selector :m |
  					| oldCodeString methodNode |
  					m fileIndex > 0 ifTrue:
  						[oldCodeString := cl sourceCodeAt: selector.
+ 						methodNode := cl newCompiler
- 						methodNode := cl compilerClass new
  											parse: oldCodeString in: cl notifying: nil.
  						oldMethods addLast: m.
  						newMethods addLast: (m copyWithTempsFromMethodNode: methodNode)]]]].
  	oldMethods asArray elementsExchangeIdentityWith: newMethods asArray.
  	oldMethods := newMethods := 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: ImageSegment>>acceptSingleMethodSource: (in category 'fileIn/Out') -----
  acceptSingleMethodSource: aDictionary
  
  	| oldClassInfo oldClassName ismeta newName actualClass selector |
  	oldClassInfo := (aDictionary at: #oldClassName) findTokens: ' '.	"'Class' or 'Class class'"
  	oldClassName := oldClassInfo first asSymbol.
  	ismeta := oldClassInfo size > 1.
  
  	"must use class var since we may not be the same guy who did the initial work"
  
  	newName := RecentlyRenamedClasses ifNil: [
  		oldClassName
  	] ifNotNil: [
  		RecentlyRenamedClasses at: oldClassName ifAbsent: [oldClassName]
  	].
  	actualClass := Smalltalk at: newName.
  	ismeta ifTrue: [actualClass := actualClass class].
+ 	selector := actualClass newParser parseSelector: (aDictionary at: #methodText).
- 	selector := actualClass parserClass new parseSelector: (aDictionary at: #methodText).
  	(actualClass compiledMethodAt: selector ifAbsent: [^self "hosed input"]) 
  		putSource: (aDictionary at: #methodText)
  		fromParseNode: nil
  		class: actualClass
  		category: (aDictionary at: #category)
  		withStamp: (aDictionary at: #changeStamp)
  		inFile: 2
  		priorMethod: nil.
  
  !

Item was changed:
  ----- Method: SmalltalkImage>>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."
  	"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 |
  	(self confirm: 'This method will preserve most temp names
  (up to about 15k characters of temporaries)
  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].
  	'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 selectorsAndMethodsDo:
  					[:selector :m |
  					| oldCodeString methodNode |
  					m fileIndex > 0 ifTrue:
  						[oldCodeString := cl sourceCodeAt: selector.
+ 						methodNode := cl newCompiler
- 						methodNode := cl compilerClass new
  											parse: oldCodeString
  											in: cl
  											notifying: nil.
  						oldMethods addLast: m.
  						newMethods addLast: (m copyWithTempsFromMethodNode: methodNode)]]]].
  	oldMethods asArray elementsExchangeIdentityWith: newMethods asArray.
  	self systemNavigation allBehaviorsDo: [:b | b zapOrganization].
  	self condenseChanges.
  	Preferences disable: #warnIfNoSourcesFile!




More information about the Squeak-dev mailing list