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

commits at source.squeak.org commits at source.squeak.org
Tue Mar 15 19:16:59 UTC 2011


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

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

Name: Monticello-cmm.426
Author: cmm
Time: 4 March 2011, 3:45:04.802 pm
UUID: d9187afa-b721-40f8-a7be-d69826c610d7
Ancestors: Monticello-cmm.425

- Added a #flushCache to the preamble because we need repository's to refresh their 'cache' so they get instances of the new MCVersionName.
- Removed MCRepository>>#versionNamed: and #versionNamed:ifAbsent:.  They are not used and, besides that, they imply that all version names are unique, which is incorrect (e.g., it should have been #versionsNamed:).
- Renamed MCFileName to MCVersionName and it now inherits from String.  This allows easier transition to first-class VersionNames from Strings.

=============== Diff against Monticello-cmm.425 ===============

Item was changed:
  (PackageInfo named: 'Monticello') preamble: 'SystemWindow allSubInstances
  	select: [ :each | each model class == MCFileRepositoryInspector ]
+ 	thenDo: [ :each | each delete ].
+ MCFileBasedRepository allSubInstances do: [ : each | each flushCache ]'!
- 	thenDo: [ :each | each delete ]'!

Item was added:
+ ----- Method: ByteString>>asMCVersionName (in category '*monticello') -----
+ asMCVersionName 
+ 	^ MCVersionName on: self!

Item was added:
+ ----- Method: MCAncestry>>names (in category 'ancestry') -----
+ names
+ 	"The names of the ancestors."
+ 	^ self ancestors collect: [ : each | each name asMCVersionName ]!

Item was removed:
- ----- Method: MCDictionaryRepository>>versionNamed:ifAbsent: (in category 'versions') -----
- versionNamed: versionName ifAbsent: aBlock
- 	"Answer the MCVersion corresponding to the given version name"
- 
- 	^dict detect:[:any| any info name = versionName] ifNone: aBlock
- !

Item was changed:
  ----- Method: MCDiffyVersion>>fileName (in category 'as yet unclassified') -----
  fileName
+ 	^ ((self class
+ 		nameForVer: info name
+ 		base: base name) , '.' , self writerClass extension) asMCVersionName!
- 	^ (self class nameForVer: info name base: base name), '.', self writerClass extension!

Item was changed:
  ----- Method: MCDirectoryRepository>>allFileNames (in category 'as yet unclassified') -----
  allFileNames
+ 	^ (directory entries sortBy: [:a :b | a modificationTime >= b modificationTime]) collect: [:ea | ea name asMCVersionName]!
- 	^ (directory entries sortBy: [:a :b | a modificationTime >= b modificationTime]) collect: [:ea | ea name]!

Item was changed:
  ----- Method: MCFileBasedRepository>>allFileNamesForVersionNamed: (in category 'private-files') -----
+ 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: aString!
- allFileNamesForVersionNamed: aString
- 	^ self filterFileNames: self readableFileNames forVersionNamed: aString!

Item was changed:
  ----- Method: MCFileBasedRepository>>allPackageNames (in category 'overriding') -----
  allPackageNames
  	| answer |
  	answer := Set new.
  	self allFileNamesOrCache do:
+ 		[ : each | answer add: each asMCVersionName packageName ].
- 		[ : each | answer add: (MCFileName on: each) packageName ].
  	^ answer!

Item was changed:
  ----- Method: MCFileBasedRepository>>allVersionNames (in category 'versions') -----
  allVersionNames
+ 	^ self readableFileNames!
- 	^ self readableFileNames collect: [:ea | self versionNameFromFileName: ea]!

Item was removed:
- ----- Method: MCFileBasedRepository>>fileNamesForPackageNamed: (in category 'versions') -----
- fileNamesForPackageNamed: packageName 
- 	^ Array streamContents:
- 		[ : stream | self allFileNamesOrCache do:
- 			[ : each | | mcFileName |
- 			mcFileName := MCFileName on: each.
- 			mcFileName packageName = packageName ifTrue: [ stream nextPut: mcFileName ] ] ]!

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

Item was changed:
  ----- Method: MCFileBasedRepository>>morphicOpen: (in category 'overriding') -----
  morphicOpen: aWorkingCopy
+ 	(MCRepositoryInspector repository: self workingCopy: aWorkingCopy)
- 	(MCFileRepositoryInspector repository: self workingCopy: aWorkingCopy)
  		show!

Item was changed:
  ----- 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 ]!
- 	| pkgs |
- 	pkgs := Dictionary new.
- 	versionNames do:
- 		[ : aVersionInfo | pkgs
- 			at: (aVersionInfo copyUpToLast: $-)
- 			put: (aVersionInfo copyAfterLast: $.) asNumber ].
- 	^ [ self allVersionNames select:
- 		[ : each | (pkgs
- 			at: (each copyUpToLast: $-)
- 			ifPresent:
- 				[ : verNumber | verNumber < (each copyAfterLast: $.) asNumber or:
- 					[ verNumber = (each copyAfterLast: $.) asNumber and:
- 						[ versionNames noneSatisfy:
- 							[ : v | v = each ] ] ] ]) == true ] ]
- 		on: Error
- 		do:
- 			[ : ex | ex return: #() ]!

Item was changed:
  ----- Method: MCFileBasedRepository>>readableFileNames (in category 'private-files') -----
  readableFileNames
+ 	"Answer an Array of MCVersionNames representing every file in this repository; first the ones from the cache (whether or not they still exist in the repository) followed by every other file in this repository that Monticello can read."
- 	"Answer an Array of Strings representing every file in this repository; first the ones from the cache (whether or not they still exist in the repository) followed by every other file in this repository that Monticello can read."
  	| all cached new |
  	all := self allFileNamesOrCache.	"from repository"
  	cached := self cachedFileNames.	"in memory"
  	new := all difference: cached.
  	^ (cached asArray, new)
  		select: [:ea | self canReadFileNamed: ea]!

Item was changed:
  ----- 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 notNil and: [v isCacheable]) ifTrue: [cache at: aString put: v].
  	^ v!

Item was removed:
- ----- Method: MCFileBasedRepository>>versionNameFromFileName: (in category 'versions') -----
- versionNameFromFileName: aString
- 	^ (aString copyUpToLast: $.) copyUpTo: $(!

Item was removed:
- ----- Method: MCFileBasedRepository>>versionNamed:ifAbsent: (in category 'versions') -----
- versionNamed: versionName ifAbsent: aBlock
- 	"Answer the MCVersion corresponding to the given version name"
- 
- 	(self allFileNamesForVersionNamed: versionName) do:[:fileName | 
- 		| version |
- 		version := self versionFromFileNamed: fileName.
- 		version info name = versionName ifTrue: [^version].
- 	].
- 	^aBlock value!

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

Item was removed:
- Object subclass: #MCFileName
- 	instanceVariableNames: 'packageName author extension versionNumber fileName ancestorAuthor ancestorVersionNumber'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Monticello-Modeling'!
- 
- !MCFileName commentStamp: 'cmm 3/2/2011 15:25' prior: 0!
- A MCFileName models the Monticello file / version name, in the format [Package]-[Author].[version-number]([ancestorAuthor.ancestorVersionNumber]).[mc?].
- 
- The final file-extension only applies to filenames, not version names.
- 
- Instance Variables
- 	author:		<String>
- 	extension:		<String>
- 	fileName:		<String>
- 	packageName:		<String>
- 	versionNumber:		<Integer>!

Item was removed:
- ----- Method: MCFileName classSide>>on: (in category 'create') -----
- on: aString 
- 	"aString may be with or without a mc? extension."
- 	^ self new
- 		filename: aString ;
- 		yourself!

Item was removed:
- ----- Method: MCFileName>>= (in category 'testing') -----
- = aMCFileName 
- 	self == aMCFileName ifTrue: [ ^ true ].
- 	self species = aMCFileName species ifFalse: [ ^ false ].
- 	^ self versionNumber = aMCFileName versionNumber and:
- 		[ self author = aMCFileName author and:
- 			[ self packageName = aMCFileName packageName and:
- 				[ self ancestorAuthor = aMCFileName ancestorAuthor and: [ self ancestorVersionNumber = aMCFileName ancestorVersionNumber ] ] ] ]!

Item was removed:
- ----- Method: MCFileName>>ancestorAuthor (in category 'access') -----
- ancestorAuthor
- 	"The author of the ancestor, if this is a Diffy filename."
- 	^ ancestorAuthor!

Item was removed:
- ----- Method: MCFileName>>ancestorVersionNumber (in category 'access') -----
- ancestorVersionNumber
- 	"The Integer versionNumber of the ancestor, if this is a Diffy filename."
- 	^ ancestorVersionNumber!

Item was removed:
- ----- Method: MCFileName>>author (in category 'access') -----
- author
- 	"The author initials embedded in the filename."
- 	^ author!

Item was removed:
- ----- Method: MCFileName>>extension (in category 'access') -----
- extension
- 	"The filename's extension."
- 	^ extension!

Item was removed:
- ----- Method: MCFileName>>fileName (in category 'access') -----
- fileName
- 	^ fileName!

Item was removed:
- ----- Method: MCFileName>>filename: (in category 'initializing') -----
- filename: aString 
- 	"Parse aString which is assumed to be either a MC filename [Package]-[author].[versionNumber]([ancestorAuthor].[ancestorVersionNumber]), with or without a .mc? extension.  The ancestorAuthor and ancestorVersionNumber are only applicable for 'diffy' names."
- 	| versionName ancestry |
- 	fileName := aString.
- 	versionName := (aString copyUpToLast: $.) copyUpTo: $(.
- 	packageName := versionName copyUpToLast: $-.
- 	author := (versionName copyAfterLast: $-) copyUpTo: $..
- 	versionNumber := versionName last isDigit
- 		ifTrue:
- 			[ extension := aString copyAfterLast: $..
- 			((versionName copyAfterLast: $-) copyAfter: $.) asInteger ifNil: [ 0 ] ]
- 		ifFalse: [ ((aString copyAfterLast: $-) copyAfter: $.) asInteger ifNil: [ 0 ] ].
- 	ancestry := (aString copyAfterLast: $() copyUpTo: $).
- 	ancestry ifNotEmpty:
- 		[ ancestorAuthor := (ancestry copyUpTo: $.).
- 		ancestorVersionNumber := ((ancestry copyAfter: $.) asInteger) ifNil: [ 0 ] ]!

Item was removed:
- ----- Method: MCFileName>>hash (in category 'testing') -----
- hash
- 	^ ((self versionNumber hash + self author hash hashMultiply) hashMultiply + self packageName hash) hashMultiply!

Item was removed:
- ----- Method: MCFileName>>isValid (in category 'testing') -----
- isValid
- 	^ {  packageName. author. versionNumber  } allSatisfy: [ : e | e notNil ]!

Item was removed:
- ----- Method: MCFileName>>packageName (in category 'access') -----
- packageName
- 	"The MC Package name embedded into this filename."
- 	^ packageName!

Item was removed:
- ----- Method: MCFileName>>printOn: (in category 'printing') -----
- printOn: aStream 
- 	super printOn: aStream.
- 	aStream
- 		 space ;
- 		 nextPutAll: self fileName!

Item was removed:
- ----- Method: MCFileName>>versionName (in category 'access') -----
- versionName
- 	"Answer my version name, without the file suffix."
- 	^ extension
- 		ifNil: [ fileName ]
- 		ifNotNil:
- 			[ String streamContents:
- 				[ : stream | stream
- 					 nextPutAll: self packageName ;
- 					 nextPut: $- ;
- 					 nextPutAll: self author ;
- 					 nextPut: $. ;
- 					 nextPutAll: self versionNumber asString ] ]!

Item was removed:
- ----- Method: MCFileName>>versionNumber (in category 'access') -----
- versionNumber
- 	"The Integer version number identified by this filename."
- 	^ versionNumber!

Item was changed:
  ----- Method: MCFtpRepository>>parseDirectoryListing: (in category 'as yet unclassified') -----
  parseDirectoryListing: aString
  	| stream files line tokens |
  	stream := aString readStream.
  	files := OrderedCollection new.
  	[stream atEnd] whileFalse:
  		[line := stream nextLine.
  		tokens := line findTokens: ' '.
+ 		tokens size > 2 ifTrue: [files add: tokens last asMCVersionName]].
- 		tokens size > 2 ifTrue: [files add: tokens last]].
  	^ files!

Item was changed:
  ----- Method: MCHttpRepository>>parseFileNamesFromStream: (in category 'as yet unclassified') -----
  parseFileNamesFromStream: aStream
  	| names fullName |
  	names := OrderedCollection new.
  	[aStream atEnd] whileFalse:
  		[[aStream upTo: $<. {$a. $A. nil} includes: aStream next] whileFalse.
  		aStream upTo: $".
  		aStream atEnd ifFalse: [
  			fullName := aStream upTo: $".
+ 			names add: fullName unescapePercents asMCVersionName ]].
- 			names add: fullName unescapePercents]].
  	^ names!

Item was changed:
+ ----- Method: MCRepository>>alwaysStoreDiffs (in category 'accessing') -----
- ----- Method: MCRepository>>alwaysStoreDiffs (in category 'as yet unclassified') -----
  alwaysStoreDiffs
  	^ storeDiffs ifNil: [false]!

Item was changed:
+ ----- Method: MCRepository>>asCreationTemplate (in category 'accessing') -----
- ----- Method: MCRepository>>asCreationTemplate (in category 'as yet unclassified') -----
  asCreationTemplate
  	^ self creationTemplate!

Item was changed:
+ ----- Method: MCRepository>>basicStoreVersion: (in category 'private') -----
- ----- Method: MCRepository>>basicStoreVersion: (in category 'as yet unclassified') -----
  basicStoreVersion: aVersion
  	self subclassResponsibility!

Item was changed:
+ ----- Method: MCRepository>>closestAncestorVersionFor:ifNone: (in category 'accessing') -----
- ----- Method: MCRepository>>closestAncestorVersionFor:ifNone: (in category 'as yet unclassified') -----
  closestAncestorVersionFor: anAncestry ifNone: errorBlock
  	anAncestry breadthFirstAncestorsDo:
  		[:ancestorInfo |
  		(self versionWithInfo: ancestorInfo) ifNotNil: [:v | ^ v]].
  	^ errorBlock value!

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

Item was changed:
+ ----- Method: MCRepository>>creationTemplate: (in category 'accessing') -----
- ----- Method: MCRepository>>creationTemplate: (in category 'as yet unclassified') -----
  creationTemplate: aString
  	self creationTemplate ifNotNil: [ self error: 'Creation template already set for this MCRepository instance.' ].
  	
  	creationTemplate := aString.!

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

Item was changed:
+ ----- Method: MCRepository>>doAlwaysStoreDiffs (in category 'accessing') -----
- ----- Method: MCRepository>>doAlwaysStoreDiffs (in category 'as yet unclassified') -----
  doAlwaysStoreDiffs
  	storeDiffs := true!

Item was changed:
+ ----- Method: MCRepository>>doNotAlwaysStoreDiffs (in category 'accessing') -----
- ----- Method: MCRepository>>doNotAlwaysStoreDiffs (in category 'as yet unclassified') -----
  doNotAlwaysStoreDiffs
  	storeDiffs := false!

Item was removed:
- ----- Method: MCRepository>>fileNamesForPackageNamed: (in category 'versions') -----
- fileNamesForPackageNamed: aString
- 	"Answer a collection of MCFileNames whose Package is named aString."
- 	self subclassResponsibility!

Item was changed:
  ----- Method: MCRepository>>highestNumberedVersionNameForPackageNamed: (in category 'versions') -----
  highestNumberedVersionNameForPackageNamed: aString 
+ 	^ (self versionNamesForPackageNamed: aString)
- 	^ (self fileNamesForPackageNamed: aString)
  		ifNil: [ self error: aString , ' not found in ' , self asString ]
  		ifNotNilDo:
  			[ : pkg | pkg detectMax:
  				[ : each | each versionNumber ] ]!

Item was changed:
+ ----- Method: MCRepository>>includesVersionNamed: (in category 'versions') -----
- ----- Method: MCRepository>>includesVersionNamed: (in category 'interface') -----
  includesVersionNamed: aString
  	self subclassResponsibility!

Item was removed:
- ----- Method: MCRepository>>initialize (in category 'initialize-release') -----
- initialize!

Item was changed:
+ ----- Method: MCRepository>>morphicOpen (in category 'ui') -----
- ----- Method: MCRepository>>morphicOpen (in category 'interface') -----
  morphicOpen
  	self morphicOpen: nil!

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

Item was changed:
+ ----- Method: MCRepository>>notificationForVersion: (in category 'accessing') -----
- ----- Method: MCRepository>>notificationForVersion: (in category 'as yet unclassified') -----
  notificationForVersion: aVersion
  	^ MCVersionNotification version: aVersion repository: self!

Item was changed:
+ ----- Method: MCRepository>>notifyList (in category 'accessing') -----
- ----- Method: MCRepository>>notifyList (in category 'as yet unclassified') -----
  notifyList
  	^ #()!

Item was changed:
+ ----- Method: MCRepository>>openAndEditTemplateCopy (in category 'ui') -----
- ----- Method: MCRepository>>openAndEditTemplateCopy (in category 'interface') -----
  openAndEditTemplateCopy
  	^ self class fillInTheBlankConfigure: (self asCreationTemplate ifNil: [^nil])!

Item was changed:
+ ----- Method: MCRepository>>possiblyNewerVersionsOfAnyOf: (in category 'versions') -----
+ possiblyNewerVersionsOfAnyOf: versionNames
+ 	self subclassResponsibility!
- ----- Method: MCRepository>>possiblyNewerVersionsOfAnyOf: (in category 'as yet unclassified') -----
- possiblyNewerVersionsOfAnyOf: someVersions
- 	^#()!

Item was changed:
+ ----- Method: MCRepository>>prepareVersionForStorage: (in category 'accessing') -----
- ----- Method: MCRepository>>prepareVersionForStorage: (in category 'as yet unclassified') -----
  prepareVersionForStorage: aVersion
  	^ self alwaysStoreDiffs
  		ifTrue: [aVersion asDiffAgainst:
  				 (self closestAncestorVersionFor: aVersion info ifNone: [^ aVersion])]
  		ifFalse: [aVersion]!

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

Item was added:
+ ----- Method: MCRepository>>refresh (in category 'accessing') -----
+ refresh
+ 	"Subclasses override if necessary."!

Item was changed:
+ ----- Method: MCRepository>>sendNotificationsForVersion: (in category 'accessing') -----
- ----- Method: MCRepository>>sendNotificationsForVersion: (in category 'as yet unclassified') -----
  sendNotificationsForVersion: aVersion
  	| notification notifyList |
  	notifyList := self notifyList.
  	notifyList isEmpty ifFalse:
  		[notification := self notificationForVersion: aVersion.
  		notifyList do: [:ea | notification notify: ea]]!

Item was changed:
+ ----- Method: MCRepository>>storeVersion: (in category 'accessing') -----
- ----- Method: MCRepository>>storeVersion: (in category 'as yet unclassified') -----
  storeVersion: aVersion
  	self basicStoreVersion: (self prepareVersionForStorage: aVersion).
  	self sendNotificationsForVersion: aVersion!

Item was removed:
- ----- Method: MCRepository>>versionNamed: (in category 'versions') -----
- versionNamed: versionName
- 	"Answer the MCVersion corresponding to the given version name"
- 
- 	^self versionNamed: versionName ifAbsent:[nil]!

Item was removed:
- ----- Method: MCRepository>>versionNamed:ifAbsent: (in category 'versions') -----
- versionNamed: versionName ifAbsent: aBlock
- 	"Answer the MCVersion corresponding to the given version name"
- 
- 	^aBlock value!

Item was added:
+ ----- Method: MCRepository>>versionNamesForPackageNamed: (in category 'versions') -----
+ versionNamesForPackageNamed: aString
+ 	"Answer a collection of MCVersionNames whose Package is named aString."
+ 	self subclassResponsibility!

Item was changed:
+ ----- Method: MCRepository>>versionWithInfo: (in category 'versions') -----
- ----- Method: MCRepository>>versionWithInfo: (in category 'interface') -----
  versionWithInfo: aVersionInfo
  	^ self versionWithInfo: aVersionInfo ifAbsent: [nil]!

Item was changed:
+ ----- Method: MCRepository>>versionWithInfo:ifAbsent: (in category 'versions') -----
- ----- Method: MCRepository>>versionWithInfo:ifAbsent: (in category 'interface') -----
  versionWithInfo: aVersionInfo ifAbsent: aBlock
  	self subclassResponsibility !

Item was changed:
  MCVersionInspector subclass: #MCRepositoryInspector
+ 	instanceVariableNames: 'repository packageNames versionNames selectedPackage selectedVersion order versionInfo loaded newer inherited'
- 	instanceVariableNames: 'repository packageNames versionNames selectedPackage selectedVersion order versionInfo'
  	classVariableNames: 'Order'
  	poolDictionaries: ''
  	category: 'Monticello-UI'!

Item was removed:
- ----- Method: MCRepositoryInspector>>hasNewerVersionsFor: (in category 'private') -----
- hasNewerVersionsFor: aMCWorkingCopy 
- 	| latest |
- 	latest := (self versionNames select:
- 		[ : eachMCFileName | eachMCFileName packageName = aMCWorkingCopy package name ]) detectMax:
- 		[ : eachMCFileName | eachMCFileName versionNumber ].
- 	^ latest notNil and:
- 		[ aMCWorkingCopy ancestors allSatisfy:
- 			[ : ancestor | | loadedVersionNumber ancestorName |
- 			ancestorName := ancestor mcName.
- 			loadedVersionNumber := ancestorName versionNumber.
- 			loadedVersionNumber < latest versionNumber or:
- 				[ loadedVersionNumber = latest versionNumber and: [ ancestorName author ~= latest author ] ] ] ]!

Item was changed:
  ----- Method: MCRepositoryInspector>>identifyLoadedAndInherited: (in category 'morphic ui') -----
  identifyLoadedAndInherited: aMCWorkingCopy 
  	aMCWorkingCopy ancestors do:
+ 		[ : ancestor | loaded add: ancestor versionName.
- 		[ : ancestor | loaded add: ancestor mcName.
  		ancestor ancestorsDoWhileTrue:
  			[ : heir | (inherited includes: heir name)
  				ifTrue: [ false ]
  				ifFalse:
+ 					[ inherited add: heir name asMCVersionName.
- 					[ inherited add: heir name.
  					true ] ] ]!

Item was added:
+ ----- Method: MCRepositoryInspector>>identifyNewerVersionsOf: (in category 'private') -----
+ identifyNewerVersionsOf: aMCWorkingCopy 
+ 	(repository possiblyNewerVersionsOfAnyOf: aMCWorkingCopy ancestry names) do:
+ 		[ : eachNewerVersionName | newer add: eachNewerVersionName packageName ]!

Item was changed:
  ----- Method: MCRepositoryInspector>>packageList (in category 'morphic ui') -----
  packageList
  	| result loadedPackages |
  	packageNames ifNotNil: [ ^ packageNames ].
+ 	"Enjoy emphasis side-effects of populating my versionNames." 
+ 	self versionNames.
  	result := repository allPackageNames.
  	"sort loaded packages first, then alphabetically"
  	loadedPackages := Set new: loaded size.
  	loaded do:
  		[ : each | loadedPackages add: each packageName ].
  	result := result asArray sort:
  		[ : a : b | | loadedA loadedB |
  		loadedA := loadedPackages includes: a.
  		loadedB := loadedPackages includes: b.
  		loadedA = loadedB
  			ifTrue: [ a < b ]
  			ifFalse: [ loadedA ] ].
  	^ packageNames := result collect:
  		[ : each | self packageHighlight: each ]!

Item was changed:
  ----- Method: MCRepositoryInspector>>refresh (in category 'actions') -----
  refresh
  	packageNames := versionNames := nil.
+ 	repository refresh.
  	self
  		 changed: #packageList ;
+ 		 changed: #versionList.!
- 		 changed: #versionList!

Item was changed:
  ----- Method: MCRepositoryInspector>>refreshEmphasis (in category 'morphic ui') -----
  refreshEmphasis
  	self initializeEmphasis.
  	MCWorkingCopy allManagers do:
+ 		[ : each | self
+ 			 identifyLoadedAndInherited: each ;
+ 			 identifyNewerVersionsOf: each ]!
- 		[ : each | | latest |
- 		self identifyLoadedAndInherited: each.
- 		(self hasNewerVersionsFor: each) ifTrue: [ newer add: each package name ] ]!

Item was changed:
  ----- Method: MCRepositoryInspector>>versionHighlight: (in category 'morphic ui') -----
+ versionHighlight: aMCVersionName
- versionHighlight: aMCFileName
  	inherited ifNil: [inherited := #()].
  	^Text
+ 		string: aMCVersionName
- 		string: aMCFileName fileName
  		attribute: (TextEmphasis new emphasisCode: (
+ 			((loaded includes: aMCVersionName) ifTrue: [ 4 "underlined" ]
+ 				ifFalse: [ (inherited includes: aMCVersionName)
- 			((loaded includes: aMCFileName) ifTrue: [ 4 "underlined" ]
- 				ifFalse: [ (inherited includes: aMCFileName versionName)
  					ifTrue: [ 0 ]
  					ifFalse: [ 1 "bold" ] ])))!

Item was changed:
  ----- Method: MCRepositoryInspector>>versionNames (in category 'private') -----
  versionNames
  	^ versionNames ifNil:
  		[ selectedPackage
  			ifNil: [ Array empty ]
  			ifNotNil:
+ 				[ versionNames := repository versionNamesForPackageNamed: selectedPackage.
- 				[ versionNames := repository fileNamesForPackageNamed: selectedPackage.
  				self refreshEmphasis.
  				versionNames ] ]!

Item was removed:
- ----- Method: MCSMCacheRepository>>allFileNames (in category 'accessing') -----
- allFileNames
- 	^self allFullFileNames collect: [ :ea | self directory localNameFor: ea ]!

Item was changed:
  ----- Method: MCVersion>>fileName (in category 'accessing') -----
  fileName
+ 	^ (info name, '.', self writerClass extension) asMCVersionName!
- 	^ info name, '.', self writerClass extension!

Item was changed:
  ----- Method: MCVersionInfo>>initializeWithName:id:message:date:time:author:ancestors:stepChildren: (in category 'initialize-release') -----
  initializeWithName: vName id: aUUID message: aString date: aDate time: aTime author: initials ancestors: aCollection stepChildren: stepCollection
+ 	name := vName asMCVersionName.
- 	name := vName.
  	id := aUUID.
  	message := aString.
  	date := aDate.
  	time := aTime.
  	author := initials.
  	ancestors :=  aCollection.
  	stepChildren := stepCollection!

Item was removed:
- ----- Method: MCVersionInfo>>mcName (in category 'accessing') -----
- mcName
- 	^ MCFileName on: self name!

Item was added:
+ ----- Method: MCVersionInfo>>versionName (in category 'accessing') -----
+ versionName
+ 	^ name
+ 		ifNil: [ self name ]
+ 		ifNotNil: [ name asMCVersionName ]!

Item was changed:
  MCTool subclass: #MCVersionInspector
+ 	instanceVariableNames: 'version'
- 	instanceVariableNames: 'version loaded newer inherited'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Monticello-UI'!

Item was added:
+ ByteString variableByteSubclass: #MCVersionName
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Monticello-Modeling'!
+ 
+ !MCVersionName commentStamp: 'cmm 3/4/2011 13:32' prior: 0!
+ A MCVersionName models the Monticello file / version name, in the format [Package]-[Author].[version-number]([ancestorAuthor.ancestorVersionNumber]).[mc?].
+ 
+ Any file-extension, if present, is ignored.!

Item was added:
+ ----- Method: MCVersionName classSide>>on: (in category 'create') -----
+ on: aString 
+ 	"aString may be with or without a mc? extension."
+ 	^ (self new: aString size)
+ 		replaceFrom: 1
+ 			to: aString size
+ 			with: aString
+ 			startingAt: 1 ;
+ 		yourself!

Item was added:
+ ----- Method: MCVersionName>>= (in category 'testing') -----
+ = aByteString 
+ 	"Ignore any file-extension for comparison of MCVersionNames."
+ 	| myVersionName |
+ 	myVersionName := self versionName.
+ 	^ (myVersionName
+ 		compare: myVersionName
+ 		with: aByteString asMCVersionName versionName
+ 		collated: AsciiOrder) = 2!

Item was added:
+ ----- Method: MCVersionName>>ancestorAuthor (in category 'access') -----
+ ancestorAuthor
+ 	"The author of the ancestor, if this is a Diffy filename."
+ 	^ self ancestry in:
+ 		[ : authorDotVersion | authorDotVersion copyUpTo: $. ]!

Item was added:
+ ----- Method: MCVersionName>>ancestorVersionNumber (in category 'access') -----
+ ancestorVersionNumber
+ 	"The author of the ancestor, if this is a Diffy filename."
+ 	^ self ancestry in:
+ 		[ : authorDotVersion | (authorDotVersion copyAfter: $.) asInteger ifNil: [ 0 ] ]!

Item was added:
+ ----- Method: MCVersionName>>ancestry (in category 'private') -----
+ ancestry
+ 	"If I am a in the diffy-format which includes the ancestor attributes, answer them as a single String, separated by a dot."
+ 	^ (self copyAfterLast: $() copyUpTo: $)!

Item was added:
+ ----- Method: MCVersionName>>asMCVersionName (in category 'converting') -----
+ asMCVersionName
+ 	^ self!

Item was added:
+ ----- Method: MCVersionName>>author (in category 'access') -----
+ author
+ 	"The author initials embedded in the filename."
+ 	^ self versionName in:
+ 		[ : verName | (verName copyAfterLast: $-) copyUpTo: $. ]!

Item was added:
+ ----- Method: MCVersionName>>hash (in category 'testing') -----
+ hash
+ 	^ self versionName hash!

Item was added:
+ ----- Method: MCVersionName>>isValid (in category 'testing') -----
+ isValid
+ 	^ [ self packageName notEmpty and:
+ 		[ self author notEmpty and: [ self versionNumber > 0 ] ] ]
+ 		on: Error
+ 		do:
+ 			[ : err | false ]!

Item was added:
+ ----- Method: MCVersionName>>packageName (in category 'access') -----
+ packageName
+ 	"The MC Package name embedded into this filename."
+ 	^ self versionName in:
+ 		[ : verName | verName copyUpToLast: $- ]!

Item was added:
+ ----- Method: MCVersionName>>species (in category 'private') -----
+ species
+ 	^ ByteString!

Item was added:
+ ----- Method: MCVersionName>>versionName (in category 'access') -----
+ versionName
+ 	"Answer my version name as a ByteString, without the file suffix or any ancestor-attributes."
+ 	^ self last isDigit
+ 		ifTrue:
+ 			[ "The whole of me, but convert to a ByteString"
+ 			self
+ 				copyFrom: 1
+ 				to: self size ]
+ 		ifFalse: [ (self copyUpToLast: $.) copyUpTo: $( ]!

Item was added:
+ ----- Method: MCVersionName>>versionNumber (in category 'access') -----
+ versionNumber
+ 	"The Integer version number identified by this filename."
+ 	^ ((self versionName copyAfterLast: $-) copyAfter: $.) asInteger ifNil: [ 0 ]!

Item was changed:
  ----- Method: MCWorkingCopy>>possiblyNewerVersionsIn: (in category 'private') -----
  possiblyNewerVersionsIn: aRepository 
  	^ aRepository possiblyNewerVersionsOfAnyOf:
  		(self ancestors collect:
+ 			[ : each | each versionName ])!
- 			[ : each | each name ])!

Item was added:
+ (PackageInfo named: 'Monticello') postscript: 'nil'!



More information about the Packages mailing list