[Pkg] The Trunk: Monticello-cmm.431.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Mar 15 19:18:25 UTC 2011


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

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

Name: Monticello-cmm.431
Author: cmm
Time: 6 March 2011, 5:08:52.968 pm
UUID: 1d845f2d-d9ab-43ba-93e3-54193c57a943
Ancestors: Monticello-cmm.430

- Hid last of "file"-based api from public categories and removed all external calls of that api.  #versionFromFileNamed: is now called #versionNamed: and is a new responsibility of any MCRepository.
- #possiblyNewerVersionsOfAnyOf: is now inherited by all MCRepository types.
- MCRepositoryInspector>>'versionInfo' was pushed down to MCFileRepositoryInspector, because it is just an optimization based on the limitations of file-based repositories.
- Updated MCGOODSRepository to be compliant with new protocol.
- Added MCRepository>>#copyAllFrom: for easy transfer of all versions from one repository to another.
- No longer required for MCRepository's to implement #morphicOpen:, generic behavior is usually sufficient.

=============== Diff against Monticello-cmm.430 ===============

Item was changed:
  ----- Method: MCDictionaryRepository>>includesVersionNamed: (in category 'as yet unclassified') -----
+ includesVersionNamed: aString 
+ 	| mcVersionName |
+ 	mcVersionName := aString asMCVersionName.
+ 	^ dict anySatisfy:
+ 		[ : ea | ea info versionName = mcVersionName ]!
- includesVersionNamed: aString
- 	^ dict anySatisfy: [:ea | ea info name = aString]!

Item was changed:
  ----- Method: MCFileBasedRepository>>allFileNamesForVersionNamed: (in category 'private-files') -----
+ allFileNamesForVersionNamed: aMCVersionName 
- allFileNamesForVersionNamed: aString 
- 	"Answer all version names matching aString.  It's rare, but possible to have more than one version with the same exact name.  In that case, only the UUID on their VersionInfo's can make the distinction."
  	^ self
  		filterFileNames: self readableFileNames
+ 		forVersionNamed: aMCVersionName!
- 		forVersionNamed: aString!

Item was changed:
+ ----- Method: MCFileBasedRepository>>allVersionNames (in category 'private-files') -----
- ----- Method: MCFileBasedRepository>>allVersionNames (in category 'versions') -----
  allVersionNames
  	^ self readableFileNames!

Item was changed:
  ----- Method: MCFileBasedRepository>>filterFileNames:forVersionNamed: (in category 'private-files') -----
+ filterFileNames: aCollection forVersionNamed: aMCVersionName 
- filterFileNames: aCollection forVersionNamed: aString 
  	^ aCollection select:
+ 		[ : ea | aMCVersionName = ea ]!
- 		[ : ea | ea = aString ]!

Item was changed:
  ----- Method: MCFileBasedRepository>>includesVersionNamed: (in category 'versions') -----
  includesVersionNamed: aString
+ 	^ self allVersionNames includes: aString asMCVersionName!
- 	^ self allVersionNames includes: aString!

Item was changed:
+ ----- Method: MCFileBasedRepository>>loadVersionFromFileNamed: (in category 'private-files') -----
- ----- Method: MCFileBasedRepository>>loadVersionFromFileNamed: (in category 'versions') -----
  loadVersionFromFileNamed: aString
  	^ self versionReaderForFileNamed: aString do: [:r | r version]!

Item was changed:
+ ----- Method: MCFileBasedRepository>>loadVersionInfoFromFileNamed: (in category 'private-files') -----
- ----- Method: MCFileBasedRepository>>loadVersionInfoFromFileNamed: (in category 'versions') -----
  loadVersionInfoFromFileNamed: aString
  	^ self versionReaderForFileNamed: aString do: [:r | r info]
  	!

Item was removed:
- ----- Method: MCFileBasedRepository>>possiblyNewerVersionsOfAnyOf: (in category 'versions') -----
- possiblyNewerVersionsOfAnyOf: versionNames 
- 	^ versionNames
- 		inject: OrderedCollection new
- 		into:
- 			[ : coll : eachVersionName | | eachPackageName |
- 			eachPackageName := eachVersionName packageName.
- 			(self versionNamesForPackageNamed: eachPackageName) do:
- 				[ : eachInSelf | (eachInSelf versionNumber > eachVersionName versionNumber or:
- 					[ eachInSelf versionNumber = eachVersionName versionNumber and: [ eachInSelf author ~= eachVersionName author ] ]) ifTrue: [ coll add: eachInSelf ] ].
- 			coll ]!

Item was removed:
- ----- Method: MCFileBasedRepository>>versionFromFileNamed: (in category 'versions') -----
- versionFromFileNamed: aString
- 	| v |
- 	v := self cache at: aString ifAbsent: [self loadVersionFromFileNamed: aString].
- 	self resizeCache: cache.
- 	(v notNil and: [v isCacheable]) ifTrue: [cache at: aString asMCVersionName put: v].
- 	^ v!

Item was changed:
+ ----- Method: MCFileBasedRepository>>versionInfoFromFileNamed: (in category 'private-files') -----
- ----- Method: MCFileBasedRepository>>versionInfoFromFileNamed: (in category 'versions') -----
  versionInfoFromFileNamed: aString
  	self cache at: aString ifPresent: [:v | ^ v info].
  	^ self loadVersionInfoFromFileNamed: aString!

Item was added:
+ ----- Method: MCFileBasedRepository>>versionNamed: (in category 'versions') -----
+ versionNamed: aMCVersionName
+ 	"For FileBased repositories, aMCVersionName must have the appropriate extension!!  :-("
+ 	| v |
+ 	v := self cache at: aMCVersionName ifAbsent: [self loadVersionFromFileNamed: aMCVersionName].
+ 	self resizeCache: cache.
+ 	(v notNil and: [v isCacheable]) ifTrue: [cache at: aMCVersionName asMCVersionName put: v].
+ 	^ v!

Item was changed:
  ----- Method: MCFileBasedRepository>>versionNamesForPackageNamed: (in category 'versions') -----
  versionNamesForPackageNamed: packageName 
  	^ Array streamContents:
  		[ : stream | self allFileNamesOrCache do:
+ 			[ : each | | mcVersionName |
+ 			mcVersionName := each asMCVersionName.
+ 			mcVersionName packageName = packageName ifTrue: [ stream nextPut: mcVersionName ] ] ]!
- 			[ : each | | mcFileName |
- 			mcFileName := each asMCVersionName.
- 			mcFileName packageName = packageName ifTrue: [ stream nextPut: mcFileName ] ] ]!

Item was changed:
+ ----- Method: MCFileBasedRepository>>versionReaderForFileNamed:do: (in category 'private-files') -----
- ----- Method: MCFileBasedRepository>>versionReaderForFileNamed:do: (in category 'versions') -----
  versionReaderForFileNamed: aString do: aBlock
  	^ self
  		readStreamForFileNamed: aString
  		do: [:s |
  			(MCVersionReader readerClassForFileNamed: aString) ifNotNil:
  				[:class | aBlock value: (class on: s fileName: aString)]]
  !

Item was changed:
  ----- Method: MCFileBasedRepository>>versionWithInfo:ifAbsent: (in category 'versions') -----
  versionWithInfo: aVersionInfo ifAbsent: errorBlock
+ 	(self allFileNamesForVersionNamed: aVersionInfo versionName) do:
- 	
- 	(self allFileNamesForVersionNamed: aVersionInfo name) do:
  		[:fileName | | version |
+ 		version := self versionNamed: fileName.
- 		version := self versionFromFileNamed: fileName.
  		version info = aVersionInfo ifTrue: [^ version]].
  	^ errorBlock value!

Item was added:
+ ----- Method: MCFileRepositoryInspector>>versionInfo (in category 'private') -----
+ versionInfo
+ 	^ versionInfo ifNil: [versionInfo := repository versionInfoFromFileNamed: selectedVersion]!

Item was added:
+ ----- Method: MCFileRepositoryInspector>>versionSelection: (in category 'private') -----
+ versionSelection: aNumber 
+ 	versionInfo := nil.
+ 	super versionSelection: aNumber!

Item was added:
+ ----- Method: MCFileRepositoryInspector>>versionSummary (in category 'morphic ui') -----
+ versionSummary
+ 	^ version
+ 		ifNotNil: [version summary]
+ 		ifNil: [self versionInfo summary]!

Item was changed:
  MCRepository subclass: #MCGOODSRepository
  	instanceVariableNames: 'hostname port connection'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Monticello-Repositories'!
+ 
+ !MCGOODSRepository commentStamp: 'cmm 3/6/2011 16:56' prior: 0!
+ A MCGOODSRepository simply stores a Dictionary of aVersionInfo-> aMCVersion.!

Item was added:
+ ----- Method: MCGOODSRepository>>allPackageNames (in category 'as yet unclassified') -----
+ allPackageNames
+ 	^ self root collect:
+ 		[ : ea | ea package name ]!

Item was added:
+ ----- Method: MCGOODSRepository>>includesVersionNamed: (in category 'as yet unclassified') -----
+ includesVersionNamed: aString 
+ 	^ (self versionNamed: aString) notNil!

Item was removed:
- ----- Method: MCGOODSRepository>>morphicOpen: (in category 'as yet unclassified') -----
- morphicOpen: aWorkingCopy
- 	(MCRepositoryInspector repository: self workingCopy: aWorkingCopy) show!

Item was removed:
- ----- Method: MCGOODSRepository>>packages (in category 'as yet unclassified') -----
- packages
- 	^ (self root collect: [:ea | ea package]) asSet asSortedCollection!

Item was added:
+ ----- Method: MCGOODSRepository>>versionNamed: (in category 'as yet unclassified') -----
+ versionNamed: aString 
+ 	| versionName |
+ 	versionName := aString asMCVersionName.
+ 	self root keysDo:
+ 		[ : each | each versionName = versionName ifTrue: [ ^ each ] ].
+ 	^ nil!

Item was added:
+ ----- Method: MCGOODSRepository>>versionNamesForPackageNamed: (in category 'as yet unclassified') -----
+ versionNamesForPackageNamed: aString 
+ 	^ Array streamContents:
+ 		[ : stream | self root keysDo:
+ 			[ : each | each versionName packageName = aString ifTrue: [ stream nextPut: each ] ] ]!

Item was removed:
- ----- Method: MCGOODSRepository>>versionsAvailableForPackage: (in category 'as yet unclassified') -----
- versionsAvailableForPackage: aPackage
- 	^ self root asArray select: [:ea | ea package = aPackage] thenCollect: [:ea | ea info]!

Item was changed:
+ ----- Method: MCPackage>>= (in category 'testing') -----
- ----- Method: MCPackage>>= (in category 'as yet unclassified') -----
  = other
  	^ other species = self species and: [other name sameAs: name]!

Item was changed:
+ ----- Method: MCPackage>>hasWorkingCopy (in category 'testing') -----
- ----- Method: MCPackage>>hasWorkingCopy (in category 'as yet unclassified') -----
  hasWorkingCopy
  	^ MCWorkingCopy registry includesKey: self!

Item was changed:
+ ----- Method: MCPackage>>hash (in category 'testing') -----
- ----- Method: MCPackage>>hash (in category 'as yet unclassified') -----
  hash
  	^ name asLowercase hash!

Item was changed:
+ ----- Method: MCPackage>>name (in category 'accessing') -----
- ----- Method: MCPackage>>name (in category 'as yet unclassified') -----
  name
  	^ name!

Item was changed:
+ ----- Method: MCPackage>>name: (in category 'accessing') -----
- ----- Method: MCPackage>>name: (in category 'as yet unclassified') -----
  name: aString
  	name := aString!

Item was changed:
+ ----- Method: MCPackage>>printOn: (in category 'printing') -----
- ----- Method: MCPackage>>printOn: (in category 'as yet unclassified') -----
  printOn: aStream
  	super printOn: aStream.
  	aStream
  		nextPut: $(;
  		nextPutAll: name;
  		nextPut: $)!

Item was changed:
+ ----- Method: MCPackage>>snapshot (in category 'input/output') -----
- ----- Method: MCPackage>>snapshot (in category 'as yet unclassified') -----
  snapshot
  	| packageInfo definitions categories |
  	packageInfo := self packageInfo.
  	definitions := OrderedCollection new.
  	categories := packageInfo systemCategories.
  	categories isEmpty ifFalse: [ definitions add: (MCOrganizationDefinition categories: categories) ].
  	packageInfo methods do: [:ea | definitions add: ea asMethodDefinition] displayingProgress: 'Snapshotting methods...'.
  	(packageInfo respondsTo: #overriddenMethods) ifTrue:
  		[packageInfo overriddenMethods
  			do: [:ea | definitions add:
  					(packageInfo changeRecordForOverriddenMethod: ea) asMethodDefinition]
  			displayingProgress: 'Searching for overrides...'].
  	packageInfo classes do: [:ea | definitions addAll: ea classDefinitions] displayingProgress: 'Snapshotting classes...'.
  	(packageInfo respondsTo: #hasPreamble) ifTrue: [
  		packageInfo hasPreamble ifTrue: [definitions add: (MCPreambleDefinition from: packageInfo)].
  		packageInfo hasPostscript ifTrue: [definitions add: (MCPostscriptDefinition from: packageInfo)].
  		packageInfo hasPreambleOfRemoval ifTrue: [definitions add: (MCRemovalPreambleDefinition from: packageInfo)].
  		packageInfo hasPostscriptOfRemoval ifTrue: [definitions add: (MCRemovalPostscriptDefinition from: packageInfo)]]. 
  	^ MCSnapshot fromDefinitions: definitions
  !

Item was changed:
+ ----- Method: MCPackage>>storeOn: (in category 'input/output') -----
- ----- Method: MCPackage>>storeOn: (in category 'as yet unclassified') -----
  storeOn: aStream
  	aStream
  		nextPutAll: 'MCPackage';
  		space; nextPutAll: 'named: '; store: name.!

Item was changed:
+ ----- Method: MCPackage>>unload (in category 'input/output') -----
- ----- Method: MCPackage>>unload (in category 'as yet unclassified') -----
  unload
  	^ self workingCopy unload!

Item was changed:
+ ----- Method: MCPackage>>workingCopy (in category 'accessing') -----
- ----- Method: MCPackage>>workingCopy (in category 'as yet unclassified') -----
  workingCopy
  	^ MCWorkingCopy forPackage: self.!

Item was added:
+ ----- Method: MCRepository>>copyAllFrom: (in category 'versions') -----
+ copyAllFrom: aMCRepository 
+ 	"Copy all MCVersions from aMCRepository to the receiver."
+ 	aMCRepository allPackageNames
+ 		do:
+ 			[ : eachPackageName | (self versionNamesForPackageNamed: eachPackageName)
+ 				do:
+ 					[ : eachVersionName | (aMCRepository versionNamed: eachVersionName) ifNotNil:
+ 						[ : ver | self storeVersion: ver ] ]
+ 				displayingProgress:
+ 					[ : eachVersionName | 'Importing ' , eachVersionName ] ]
+ 		displayingProgress:
+ 			[ : eachPackageName | 'Importing versions of ' , eachPackageName ]!

Item was changed:
  ----- Method: MCRepository>>morphicOpen: (in category 'ui') -----
  morphicOpen: aWorkingCopy
+ 	(MCRepositoryInspector repository: self workingCopy: aWorkingCopy) show!
- 	self subclassResponsibility !

Item was changed:
  ----- Method: MCRepository>>possiblyNewerVersionsOfAnyOf: (in category 'versions') -----
+ possiblyNewerVersionsOfAnyOf: versionNames 
+ 	^ versionNames
+ 		inject: OrderedCollection new
+ 		into:
+ 			[ : coll : eachVersionName | | eachPackageName |
+ 			eachPackageName := eachVersionName packageName.
+ 			(self versionNamesForPackageNamed: eachPackageName) do:
+ 				[ : eachInSelf | (eachInSelf versionNumber > eachVersionName versionNumber or:
+ 					[ eachInSelf versionNumber = eachVersionName versionNumber and: [ eachInSelf author ~= eachVersionName author ] ]) ifTrue: [ coll add: eachInSelf ] ].
+ 			coll ]!
- possiblyNewerVersionsOfAnyOf: versionNames
- 	self subclassResponsibility!

Item was added:
+ ----- Method: MCRepository>>versionNamed: (in category 'versions') -----
+ versionNamed: aMCVersionName
+ 	"Answer the MCVersion with name, aMCVersionName, or nil if it doesn't exist in this repository."
+ 	self subclassResponsibility!

Item was changed:
  ----- Method: MCRepositoryGroup>>includesVersionNamed: (in category 'as yet unclassified') -----
+ includesVersionNamed: aString 
+ 	| versionName |
+ 	versionName := aString asMCVersionName.
+ 	self repositoriesDo:
+ 		[ : ea | (ea includesVersionNamed: versionName) ifTrue: [ ^ true ] ].
+ 	^ false!
- includesVersionNamed: aString
- 	self repositoriesDo: [:ea | (ea includesVersionNamed: aString) ifTrue: [^ true]].
- 	^ false	!

Item was changed:
  ----- Method: MCRepositoryInspector>>version (in category 'morphic ui') -----
  version
  	^ version ifNil:
  		[Cursor wait showWhile:
+ 			[version := repository versionNamed: selectedVersion].
- 			[version := repository versionFromFileNamed: selectedVersion].
  		version]!

Item was removed:
- ----- Method: MCRepositoryInspector>>versionInfo (in category 'morphic ui') -----
- versionInfo
- 	^ versionInfo ifNil: [versionInfo := repository versionInfoFromFileNamed: selectedVersion]!

Item was changed:
  ----- Method: MCRepositoryInspector>>versionSelection: (in category 'morphic ui') -----
+ versionSelection: aNumber 
+ 	selectedVersion := version := nil.
+ 	aNumber isZero ifFalse: [ selectedVersion := (self versionList at: aNumber) asString ].
+ 	self
+ 		 changed: #versionSelection ;
+ 		 changed: #summary ;
+ 		 changed: #hasVersion!
- versionSelection: aNumber
- 	aNumber isZero 
- 		ifTrue: [ selectedVersion := version := versionInfo := nil ]
- 		ifFalse: [ 
- 			selectedVersion := (self versionList at: aNumber) asString.
- 			version := versionInfo := nil].
- 	self changed: #versionSelection; changed: #summary; changed: #hasVersion!

Item was removed:
- ----- Method: MCRepositoryInspector>>versionSummary (in category 'morphic ui') -----
- versionSummary
- 	^ version
- 		ifNotNil: [version summary]
- 		ifNil: [self versionInfo summary]!



More information about the Packages mailing list