[squeak-dev] The Inbox: Monticello-cmm.699.mcz

commits at source.squeak.org commits at source.squeak.org
Mon Apr 22 19:33:20 UTC 2019


Chris Muller uploaded a new version of Monticello to project The Inbox:
http://source.squeak.org/inbox/Monticello-cmm.699.mcz

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

Name: Monticello-cmm.699
Author: cmm
Time: 22 April 2019, 2:33:18.479505 pm
UUID: de205c9e-af00-4954-9f2a-243d83ac9f1e
Ancestors: Monticello-nice.695

- Fix revisions of class definitions when there's another PackageInfo defined whose full name is only a prefix of the working copy the selected class belongs to.
- Check the local package-cache before hitting the server for operations where the ancestral UUID is known, such as diffing from the History list.  Keep its allFileNamesCache up to date.

=============== Diff against Monticello-nice.695 ===============

Item was removed:
- (PackageInfo named: 'Monticello') preamble: '"Woops, somehow missed the #browseMcMethodRevisions Service."
- 	| methodMenuServiceCategory classMenuServiceCategory |
- 	methodMenuServiceCategory := ServiceRegistry current serviceWithId: #browserMethodMenu.
- 	methodMenuServiceCategory services copy do:
- 		[ : each | (#(#browseMcMethodHistory #browseMcMethodOrigin ) includes: each id) ifTrue: [ methodMenuServiceCategory services remove: each ] ].
- 	classMenuServiceCategory := ServiceRegistry current serviceWithId: #browserClassMenu.
- 	classMenuServiceCategory services copy do:
- 		[ : each | (#(#browseMcClassHistory #browseMcClassOrigin ) includes: each id) ifTrue: [ classMenuServiceCategory services remove: each ] ]'!

Item was changed:
  ----- Method: Class>>packageInfo (in category '*monticello') -----
  packageInfo
+ 	^ (PackageInfo allPackages select: [ : each | each includesClass: self ])
+ 		ifEmpty: [ nil ]
+ 		ifNotEmpty:
+ 			[ : myPackages | "Select the most-qualified match."
+ 			myPackages detectMax: [ : each | each packageName size ] ]!
- 	^ PackageInfo allPackages
- 		detect: [ : each | each includesClass: self ]
- 		ifNone: [ nil ]!

Item was removed:
- ----- Method: MCRepository>>isTrunkBackup (in category 'testing') -----
- isTrunkBackup
- 	^ false!

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

Item was added:
+ ----- Method: MCRepository>>withCache (in category 'accessing') -----
+ withCache
+ 	"Answer the receiver with package-cache in front of it."
+ 	^ MCRepositoryGroup with: self!

Item was added:
+ ----- Method: MCRepositoryGroup class>>with: (in category 'instance creation') -----
+ with: aMCRepository 
+ 	^ self new
+ 		 addRepository: aMCRepository ;
+ 		 yourself!

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

Item was changed:
  ----- Method: MCRepositoryGroup>>flushAllFilenames (in category 'private') -----
  flushAllFilenames
+ 	self repositories do: [ : each | each flushAllFilenames ]!
- 	repositories do: [ : each | each flushAllFilenames ]!

Item was changed:
  ----- Method: MCRepositoryGroup>>versionWithInfo:ifAbsent: (in category 'repository-api') -----
  versionWithInfo: aVersionInfo ifAbsent: aBlock 
+ 	self repositories do:
- 	repositories do:
  		[ : each | ([each
  			versionWithInfo: aVersionInfo
  			ifAbsent: [ nil ]] on: NetworkError do: [ : err | nil ]) ifNotNil:
  			[ : ver | ^ ver ] ].
  	^ aBlock value!

Item was added:
+ ----- Method: MCRepositoryGroup>>withCache (in category 'accessing') -----
+ withCache
+ 	^ self!

Item was changed:
  ----- Method: MCVersionNotification>>initializeWithVersion:repository: (in category 'private') -----
  initializeWithVersion: aVersion repository: aRepository
  	version := aVersion.
  	repository := aRepository.
+ 	ancestor := repository withCache closestAncestorVersionFor: version info ifNone: []. 
- 	ancestor := repository closestAncestorVersionFor: version info ifNone: []. 
  	changes := ancestor
  				ifNil: [#()]
  				ifNotNil: [(version snapshot patchRelativeToBase: ancestor snapshot) 							operations sorted]!

Item was changed:
  ----- Method: MCWorkingCopy>>changesRelativeToRepository: (in category 'operations') -----
+ changesRelativeToRepository: aRepository 
- changesRelativeToRepository: aRepository
  	| ancestorVersion ancestorSnapshot |
+ 	ancestorVersion := aRepository withCache
+ 		closestAncestorVersionFor: ancestry
+ 		ifNone: [ nil ].
+ 	ancestorSnapshot := ancestorVersion
+ 		ifNil: [ MCSnapshot empty ]
+ 		ifNotNil: [ ancestorVersion snapshot ].
- 	ancestorVersion := aRepository closestAncestorVersionFor: ancestry ifNone: [].
- 	ancestorSnapshot := ancestorVersion ifNil: [MCSnapshot empty] ifNotNil: [ancestorVersion snapshot].
  	^ package snapshot patchRelativeToBase: ancestorSnapshot!

Item was changed:
  ----- Method: MCWorkingCopyBrowser>>viewChanges (in category 'actions') -----
  viewChanges
  	| patch |
  	self canSave ifTrue:
+ 		[patch := workingCopy changesRelativeToRepository: self repository withCache.
+ 		patch isNil ifTrue: [ ^self ].
- 		[patch := workingCopy changesRelativeToRepository: self repository.
- 		patch isNil ifTrue: [^ self].
  		patch isEmpty
  			ifTrue: [ workingCopy modified: false.
  				self inform: 'No changes' ]
  			ifFalse:
  				[ workingCopy modified: true.
  				(MCPatchBrowser forPatch: patch)
  					label: 'Patch Browser: ', workingCopy description;
  					environmentInDisplayingImage: workingCopy environment;
+ 					show ] ]!
- 					show]]!

Item was removed:
- (PackageInfo named: 'Monticello') postscript: 'MCDefinitionIndex migrateAllInstances'!



More information about the Squeak-dev mailing list