[Vm-dev] VM Maker: Cog-eem.209.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Oct 9 17:14:35 UTC 2014


Eliot Miranda uploaded a new version of Cog to project VM Maker:
http://source.squeak.org/VMMaker/Cog-eem.209.mcz

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

Name: Cog-eem.209
Author: eem
Time: 9 October 2014, 10:14:14.934 am
UUID: b544023f-6c30-4b5f-96cb-35a9014e7cfb
Ancestors: Cog-eem.208

Update Spur Monticello Paackage Patching to get
the ancestry right, with a Spur package inheriting
from both the non-Spur pachage it is derived from
and the previous Spur package, if it exists.

Provide a one-time patchAndUploadAllInTrunk to be
used to correct the ancestry of the previous patched
versions in trunk that have broken ancestry.

=============== Diff against Cog-eem.208 ===============

Item was added:
+ ----- Method: SpurBootstrapMonticelloPackagePatcher>>cachedNonDiffyVersionNamed:from: (in category 'patching') -----
+ cachedNonDiffyVersionNamed: versionName from: repo
+ 	"Make sure that the cache contains a non-diffy version of versionName and  answer it."
+ 	| cacheRepo nonDiffyVersion |
+ 	self assert: (versionName endsWith: '.mcz').
+ 	cacheRepo := MCCacheRepository default.
+ 	"Make sure that at least the diffy (.mcd) version is present"
+ 	(cacheRepo directory includesKey: versionName) ifFalse:
+ 		[cacheRepo storeVersion: (repo versionNamed: versionName)].
+ 	"if after storeVersion there's still no .mcz we need to create one; sigh..."
+ 	(cacheRepo directory includesKey: versionName) ifFalse:
+ 		[| baseName diffyVersionName diffyVersion file delete |
+ 		 baseName := versionName allButLast: 4. "strip .mcz"
+ 		 diffyVersionName := cacheRepo directory fileNames detect: [:fn| (fn endsWith: '.mcd') and: [(fn copyUpTo: $() = baseName]].
+ 		 diffyVersion := cacheRepo versionNamed: diffyVersionName.
+ 		 file := cacheRepo directory newFileNamed: versionName.
+ 		 delete := false.
+ 		 [file binary.
+ 		  [MCMczWriter fileOut: diffyVersion on: file]
+ 			on: Error
+ 			do: [:ex|
+ 				delete := true. "don't leave half-formed .mcz files around to screw things up later on..."
+ 				ex pass]]
+ 			ensure:
+ 				[file close.
+ 				 delete ifTrue:
+ 					[cacheRepo directory deleteFileNamed: versionName]].
+ 		 "now delete the damn diffy version that caused all the pain in the first place"
+ 		 delete ifFalse:
+ 			[cacheRepo directory deleteFileNamed: diffyVersionName].
+ 		 cacheRepo flushCache; cacheAllFilenames].
+ 	nonDiffyVersion := cacheRepo versionNamed: versionName.
+ 	self assert: (nonDiffyVersion fileName endsWith: '.mcz').
+ 	^nonDiffyVersion!

Item was added:
+ ----- Method: SpurBootstrapMonticelloPackagePatcher>>patchAndUploadAllInTrunk (in category 'patching') -----
+ patchAndUploadAllInTrunk
+ 	"Look for all versions in the default repository that have patched versions there-in.
+ 	 Download and patch them and upload the patched versions (overwriting the older ones)."
+ 	"(SpurBootstrapMonticelloPackagePatcher new
+ 		from: 'spurpackages'
+ 		to: 'trunkpackages')
+ 			patchAndUploadAllInTrunk"
+ 	| seed trunk sourceRepo cacheRepo |
+ 	seed := 'Are you really sure you want to do this?\It should happen only once!!' withCRs.
+ 	3 timesRepeat:
+ 		[(UIManager confirm: seed) ifFalse: [^self].
+ 		 seed := seed copyReplaceAll: 'really ' with: 'really, really '].
+ 	sourceDir assureExistence; deleteLocalFiles.
+ 	destDir assureExistence; deleteLocalFiles.
+ 	sourceRepo := MCDirectoryRepository directory: sourceDir.
+ 	cacheRepo := MCCacheRepository default.
+ 	(trunk := self trunk) cacheAllFileNamesDuring:
+ 		[| latestBranches latestUnbranched |
+ 		latestBranches := self packagesAndPatches keys collect:
+ 							[:package|
+ 							(trunk versionNamesForPackageNamed: package name, '.spur') detectMin: [:vn | vn asMCVersionName versionNumber]].
+ 		latestUnbranched := latestBranches collect: [:verName| (trunk versionNamed: (verName copyReplaceAll: '.spur' with: '') asMCVersionName) info ancestors first versionName].
+ 		((trunk possiblyNewerVersionsOfAnyOf: latestUnbranched)
+ 			reject: [:unpatched| unpatched includesSubString: '.spur'])
+ 			do: [:unpatched|
+ 				"it is claimed that whether a repository contains a .mcz or a .mcd is irrelevant.  At least for the cache repositoriy that's not true."
+ 				sourceRepo storeVersion: (self cachedNonDiffyVersionNamed: unpatched from: trunk)].
+ 		 self patchAsNeeded.
+ 		 self uploadFrom: (MCDirectoryRepository directory: destDir) to: trunk]!

Item was changed:
  ----- Method: SpurBootstrapMonticelloPackagePatcher>>patchAndUploadUnpatchedInTrunk (in category 'patching') -----
  patchAndUploadUnpatchedInTrunk
  	"Look for unbranched versions in the default repository that are newer than the
  	 latest patched versions there-in. Download and patch them and upload the patched
  	 versions."
  	"(SpurBootstrapMonticelloPackagePatcher new
  		from: 'spurpackages'
  		to: 'trunkpackages')
  			patchAndUploadUnpatchedInTrunk"
+ 	| trunk sourceRepo cacheRepo |
- 	| trunk sourceRepo |
  	sourceDir assureExistence; deleteLocalFiles.
  	destDir assureExistence; deleteLocalFiles.
  	sourceRepo := MCDirectoryRepository directory: sourceDir.
+ 	cacheRepo := MCCacheRepository default.
  	(trunk := self trunk) cacheAllFileNamesDuring:
  		[| latestBranches latestUnbranched |
  		latestBranches := self packagesAndPatches keys collect:
  							[:package|
  							(trunk versionNamesForPackageNamed: package name, '.spur') detectMax: [:vn | vn asMCVersionName versionNumber]].
  		latestUnbranched := latestBranches collect: [:verName| (verName copyReplaceAll: '.spur' with: '') asMCVersionName].
+ 		((trunk possiblyNewerVersionsOfAnyOf: latestUnbranched)
+ 			reject: [:unpatched| unpatched includesSubString: '.spur'])
+ 			do: [:unpatched|
+ 				"it is claimed that whether a repository contains a .mcz or a .mcd is irrelevant.  At least for the cache repositoriy that's not true."
+ 				sourceRepo storeVersion: (self cachedNonDiffyVersionNamed: unpatched from: trunk)].
- 		(trunk possiblyNewerVersionsOfAnyOf: latestUnbranched) do:
- 			[:unpatched|
- 			sourceRepo storeVersion: (trunk versionNamed: unpatched)].
  		 self patchAsNeeded.
  		 self uploadFrom: (MCDirectoryRepository directory: destDir) to: trunk]!

Item was changed:
  ----- Method: SpurBootstrapMonticelloPackagePatcher>>patchForPackage:withPatches:snapshot: (in category 'patching') -----
  patchForPackage: package withPatches: patches snapshot: snapshot
  	(package includesClass: Character) ifTrue:
  		[patches
  			addAll: ((self modifiedCharacterDefinitionsIn: snapshot definitions)
  						select:
  							[:def|
  							 patches noneSatisfy:
  								[:addition|
  								def isMethodDefinition
+ 								and: [addition definition isMethodDefinition
  								and: [addition definition selector = def selector
  								and: [addition definition className = def className
+ 								and: [addition definition classIsMeta = def classIsMeta]]]]]]
- 								and: [addition definition classIsMeta = def classIsMeta]]]]]
  						thenCollect:
  							[:def|
  							 ((def source includesSubString: 'DELETEME')
  								ifTrue: [MCRemoval]
  								ifFalse: [MCAddition]) of: def]);
  			add: (self immediateClassDefinitionFor: #Character
  					from: snapshot definitions
  					comment: 'I represent a character by storing its associated Unicode as an unsigned 30-bit value.  Characters are created uniquely, so that all instances of a particular Unicode are identical.  My instances are encoded in tagged pointers in the VM, so called immediates, and therefore are pure immutable values.
  
  	The code point is based on Unicode.  Since Unicode is 21-bit wide character set, we have several bits available for other information.  As the Unicode Standard  states, a Unicode code point doesn''t carry the language information.  This is going to be a problem with the languages so called CJK (Chinese, Japanese, Korean.  Or often CJKV including Vietnamese).  Since the characters of those languages are unified and given the same code point, it is impossible to display a bare Unicode code point in an inspector or such tools.  To utilize the extra available bits, we use them for identifying the languages.  Since the old implementation uses the bits to identify the character encoding, the bits are sometimes called "encoding tag" or neutrally "leading char", but the bits rigidly denotes the concept of languages.
  
  	The other languages can have the language tag if you like.  This will help to break the large default font (font set) into separately loadable chunk of fonts.  However, it is open to the each native speakers and writers to decide how to define the character equality, since the same Unicode code point may have different language tag thus simple #= comparison may return false.'
  					stamp: 'eem 8/12/2014 14:53')].
  	(package includesClass: SmallInteger) ifTrue:
  		[patches
  			add: (self
  					immediateClassDefinitionFor: #SmallInteger
  					from: snapshot definitions
  					comment: 'My instances are 31-bit numbers, stored in twos complement form. The allowable range is approximately +- 1 billion (see SmallInteger minVal, maxVal).  My instances are encoded in tagged pointers in the VM, so called immediates, and therefore are pure immutable values.'
  					stamp: 'eem 8/12/2014 14:54')].
  	(package includesClass: CompiledMethod) ifTrue:
  		[patches
  			add: (self compiledMethodClassDefinition)].
  	^MCPatch operations: patches!

Item was changed:
  ----- Method: SpurBootstrapMonticelloPackagePatcher>>patchPackage:with:for: (in category 'patching') -----
  patchPackage: packageFileName with: patches for: package
  	| version newVersion |
+ 	version := self versionFor: packageFileName in: sourceDir.
- 	version := self versionFor: packageFileName.
  	newVersion := self version: version withPatches: patches for: package.
  	self storeVersion: newVersion!

Item was removed:
- ----- Method: SpurBootstrapMonticelloPackagePatcher>>updateTrunkRepository (in category 'repository population') -----
- updateTrunkRepository
- 	"Download all the Collections, Kernel and System packages from trunk into srcDir,
- 	 patch them into destDir,
- 	 upload the patched and branched files that aren't already in trunk to trunk."
- 	"self new from: 'trunkpackages' to: 'spurpackages'; updateTrunkRepository"
- 	"AndreasSystemProfiler spyOn: [self new from: 'trunkpackages' to: 'spurpackages'; updateSpurRepository]"
- 	sourceDir assureExistence.
- 	self download: self class squeak45baseline from: self trunk.
- 	destDir assureExistence.
- 	self patchAsNeeded.
- 	self uploadFrom: (MCDirectoryRepository directory: destDir) to: self trunk!

Item was changed:
  ----- Method: SpurBootstrapMonticelloPackagePatcher>>version:withPatches:for: (in category 'patching') -----
  version: version withPatches: patches for: package
+ 	| snapshot ancestry possibleSpurAncestor actualAncestor |
- 	| snapshot ancestry |
  	snapshot := MCPatcher
  					apply: (self patchForPackage: package withPatches: patches snapshot: version snapshot)
  					to: version snapshot.
  	ancestry := MCWorkingAncestry new addAncestor: version info.
+ 	"this is a hack; we may not be patching w.r.t. a directory or trunk"
+ 	possibleSpurAncestor := (self spurBranchNameForInfo: version info ancestors first package: package) , '.mcz'.
+ 	(destDir includesKey: possibleSpurAncestor)
+ 		ifTrue:
+ 			[actualAncestor := self versionFor: possibleSpurAncestor in: destDir]
+ 		ifFalse:
+ 			[((self trunk versionNamesForPackageNamed: package name) includes: possibleSpurAncestor) ifTrue:
+ 				[actualAncestor := self trunk versionNamed: possibleSpurAncestor]].
+ 	actualAncestor ifNotNil:
+ 		[ancestry addAncestor: actualAncestor info].
  	^MCVersion
  		package: version package
  		info: (ancestry
  				infoWithName: (self spurBranchNameForInfo: version info package: package)
  				message:	version info name,
  							' patched for Spur by ',
  							(CCodeGenerator shortMonticelloDescriptionForClass: self class),
  							'\\' withCRs,
  							version info message)
  		snapshot: snapshot
+ 		dependencies: {} "punt on computing dependencies; there are't any so far"!
- 		dependencies: {} "punt on computing dependencies; there are't any so far"
- !

Item was removed:
- ----- Method: SpurBootstrapMonticelloPackagePatcher>>versionFor: (in category 'patching') -----
- versionFor: packageFileName
- 	^sourceDir
- 		readOnlyFileNamed: packageFileName
- 		do: [:fs|
- 			((MCVersionReader readerClassForFileNamed: fs fullName)
- 				on: fs fileName: fs fullName)
- 					version]!

Item was added:
+ ----- Method: SpurBootstrapMonticelloPackagePatcher>>versionFor:in: (in category 'patching') -----
+ versionFor: packageFileName in: directory
+ 	^directory
+ 		readOnlyFileNamed: packageFileName
+ 		do: [:fs|
+ 			((MCVersionReader readerClassForFileNamed: fs fullName)
+ 				on: fs fileName: fs fullName)
+ 					version]!



More information about the Vm-dev mailing list