[squeak-dev] The Trunk: System-cmm.668.mcz

commits at source.squeak.org commits at source.squeak.org
Mon Mar 17 01:41:12 UTC 2014


Chris Muller uploaded a new version of System to project The Trunk:
http://source.squeak.org/trunk/System-cmm.668.mcz

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

Name: System-cmm.668
Author: cmm
Time: 16 March 2014, 8:40:25.265 pm
UUID: 5ce12f1b-ffdc-46a3-8621-82a592a12377
Ancestors: System-cmm.667

- Fix to SmalltalkImage>>#sourcesName allows appending the changes to the sources file (via Levente's SmalltalkImage>>#appendChangesTo:) to work.
- Added #moveChanges as this should become a normal part of the release process.
- Some categorizations.

=============== Diff against System-cmm.667 ===============

Item was changed:
+ ----- Method: SmalltalkImage>>aboutThisSystem (in category 'miscellaneous') -----
- ----- Method: SmalltalkImage>>aboutThisSystem (in category 'sources, changes log') -----
  aboutThisSystem 
  	"Identify software version"
  
  	^self globals
  		at: #SystemReporter
  		ifPresent: [:sys | sys open]
  		ifAbsent: [self inform: self systemInformationString withCRs]!

Item was changed:
+ ----- Method: SmalltalkImage>>appendChangesTo: (in category 'sources, changes log') -----
- ----- Method: SmalltalkImage>>appendChangesTo: (in category 'housekeeping') -----
  appendChangesTo: sourcesName
  
  	"Condense changes to the end of the given sources file.
  	If the file is the same as Smalltalk sourcesName, then just append
  	the changes. If the file is different, then copy the sources file and
  	append the changes afterwards."
  
  	"Smalltalk appendChangesTo: 'test123.sources'"
  
  	"To verify correctness of the operation run the following code:
  	[	| sourceMap |
  		sourceMap := Dictionary new.
  
  		(CompiledMethod allInstances select:[:cm| cm isInstalled]) do:[:cm|
  			sourceMap at: cm methodReference put: 
  				(cm getSourceFor: cm selector in: cm methodClass)].
  		Smalltalk allClassesAndTraitsDo:[:aClass|
  			sourceMap at: aClass put: aClass comment].
  
  		Smalltalk appendChangesTo: 'verify.sources'.
  
  		(CompiledMethod allInstances select:[:cm| cm isInstalled]) do:[:cm|
  			self assert: (sourceMap at: cm methodReference) =
  				(cm getSourceFor: cm selector in: cm methodClass)].
  		Smalltalk allClassesAndTraitsDo:[:aClass|
  			self assert: (sourceMap at: aClass) = aClass comment].
  	]"
  
  	| fullName sourcesFile |
  	fullName := FileDirectory default fullNameFor: sourcesName.
+ 	(fullName endsWith: '.sources') ifFalse: [ fullName := fullName , '.sources' ].
- 	(fullName endsWith: '.sources') ifFalse:[self error: 'New name must end with .sources'].
  	fullName = Smalltalk sourcesName ifFalse:[
  		"Copy sources file; change file name accordingly"
+ 		FileStream forceNewFileNamed: fullName do: [ :newFile |
- 		FileStream forceNewFileNamed: fullName do:[:newFile| | bufSize |
- 			bufSize := 16r10000.
  			sourcesFile := (SourceFiles at: 1) readOnlyCopy.
+ 			FileDirectory default copyFile: sourcesFile toFile: newFile.
+ 			sourcesFile position: 0 ].
- 			sourcesFile position: 0.
- 			'Copying sources...'
- 				displayProgressFrom: 0 to: sourcesFile size during:[:bar|
- 					[sourcesFile atEnd] whileFalse:[
- 						bar value: sourcesFile position.
- 						newFile nextPutAll: (sourcesFile next: bufSize)]].
- 			newFile position = sourcesFile size ifFalse:[self error: 'File copy failed'].
- 		].
  		self setMacFileInfoOn: fullName.
  		"Change to the new sources file and reopen"
+ 		self 
+ 			closeSourceFiles ;
+ 			sourceFileVersionString: ((FileDirectory localNameFor: fullName) allButLast: '.sources' size) ;
+ 			openSourceFiles.
- 		self closeSourceFiles.
- 		SourceFileVersionString := (FileDirectory localNameFor: fullName) 
- 			allButLast: '.sources' size.
- 		self openSourceFiles.
  	].
  
  	"We've copied the old to the new sources file; reopen the sources file read/write"
  	sourcesFile := SourceFiles at: 1.
  	sourcesFile close; open: sourcesFile fullName forWrite: true. "should be openReadWrite"
+ 	sourcesFile setToEnd; timeStamp "remember when we did this".
- 	sourcesFile setToEnd; timeStamp. "remember when we did this"
  
  	"Copy method sources from changes to sources"
  	CompiledMethod allInstances do:[:method|
  		(method isInstalled and:[method fileIndex = 2]) ifTrue:[
  			| class selector category preamble changeList index chgRec string source |
  			class := method methodClass.
  			selector := method selector.
  			source := class sourceCodeAt: selector.
  			category := class organization categoryOfElement: selector.
  			preamble := class name, ' methodsFor: ', category asString printString,
  							' stamp: ', method timeStamp printString.
  
  			"Find the last version in the sources file; link up the prior: version"
  			changeList := ChangeSet scanVersionsOf: method 
  				class: class meta: class isMeta category: category  selector: selector.
  			index := changeList findLast:[:any| any fileIndex = 1].
  			index > 0 ifTrue:[
  				chgRec := changeList at: index.
  				preamble := preamble, ' prior: ', (SourceFiles 
  					sourcePointerFromFileIndex: chgRec fileIndex 
  					andPosition: chgRec position) printString].
  
  			"append to sources file"
  			sourcesFile setToEnd; cr; nextPut: $!!; nextChunkPut: preamble; cr.
  			string := RemoteString newString: source onFileNumber: 1 toFile: sourcesFile.
  			sourcesFile nextChunkPut: ' '.
  			method setSourcePosition: string position inFile: 1
  		].
  	] displayingProgress: 'Moving changes...'.
  
  	"Copy class comments from changes to sources"
  	self  allClassesAndTraitsDo: [:classOrTrait | 
  		classOrTrait moveClassCommentTo: sourcesFile fileIndex: 1.
  	].
  
  	"We've moved everything; reopen the source files"
  	self closeSourceFiles; openSourceFiles.
  
+ 	"Former changes are now in .sources, no need for them in .changes.  Condense them."
+ 	self condenseChanges!
- 	"Finally, run condenseChanges -- they *should* be empty 
- 	but it's better to be safe than sorry"
- 	self condenseChanges.
- !

Item was changed:
+ ----- Method: SmalltalkImage>>currentProjectDo: (in category 'miscellaneous') -----
- ----- Method: SmalltalkImage>>currentProjectDo: (in category 'sources, changes log') -----
  currentProjectDo: aBlock 
  	"So that code can work after removal of Projects"
  	self
  		at: #Project
  		ifPresent: [:projClass | aBlock value: projClass current]!

Item was added:
+ ----- Method: SmalltalkImage>>locateSourcesEntry (in category 'image, changes names') -----
+ locateSourcesEntry
+ 	| sourcesFilename |
+ 	sourcesFilename := SourceFileVersionString , FileDirectory dot , 'sources'.
+ 	^ {Smalltalk vmPath. 
+ 	FileDirectory default fullName, FileDirectory slash}
+ 		detect: [ : each | (each , sourcesFilename) asDirectoryEntry notNil ]
+ 		ifFound: [ : foundPath | (foundPath , sourcesFilename) asDirectoryEntry ]
+ 		ifNone: [ nil ]!

Item was added:
+ ----- Method: SmalltalkImage>>moveChanges (in category 'housekeeping') -----
+ moveChanges
+ 	"Move the current version of every method in .changes to my .sources file."
+ 	self appendChangesTo: self sourceFileVersionString!

Item was changed:
+ ----- Method: SmalltalkImage>>setMacFileInfoOn: (in category 'sources, changes log') -----
- ----- Method: SmalltalkImage>>setMacFileInfoOn: (in category 'miscellaneous') -----
  setMacFileInfoOn: aString
  	"On Mac, set the file type and creator (noop on other platforms)"
  	FileDirectory default
  		setMacFileNamed: aString
  		type: 'STch'
  		creator: 'FAST'.!

Item was changed:
+ ----- Method: SmalltalkImage>>sourceFileVersionString: (in category 'image, changes names') -----
- ----- Method: SmalltalkImage>>sourceFileVersionString: (in category 'miscellaneous') -----
  sourceFileVersionString: aString
  
  	SourceFileVersionString := aString!

Item was changed:
  ----- Method: SmalltalkImage>>sourcesName (in category 'image, changes names') -----
  sourcesName
+ 	"Answer the full path to the version-stable source code if it exists, otherwise the desired location"
+ 	^ self locateSourcesEntry
+ 		ifNil: [ self vmPath , SourceFileVersionString , FileDirectory dot , 'sources' ]
+ 		ifNotNil: [ : entry | entry fullName ]!
- 	"Answer the full path to the version-stable source code"
- 	^ self vmPath , SourceFileVersionString , FileDirectory dot , 'sources'!



More information about the Squeak-dev mailing list