[squeak-dev] The Trunk: MonticelloConfigurations-ct.171.mcz

commits at source.squeak.org commits at source.squeak.org
Mon Jan 3 21:00:56 UTC 2022


Christoph Thiede uploaded a new version of MonticelloConfigurations to project The Trunk:
http://source.squeak.org/trunk/MonticelloConfigurations-ct.171.mcz

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

Name: MonticelloConfigurations-ct.171
Author: ct
Time: 3 January 2022, 10:00:53.373397 pm
UUID: 40c81102-910c-0348-ba1a-26ee8781b2dc
Ancestors: MonticelloConfigurations-mt.170

Improves multilingual support.

=============== Diff against MonticelloConfigurations-mt.170 ===============

Item was changed:
  ----- Method: MCConfiguration>>depsSatisfying:versionDo:displayingProgress: (in category 'private') -----
  depsSatisfying: selectBlock versionDo: verBlock displayingProgress: progressString 
  	| count selectedVersions cleanWorkingCopies |
  	self cacheAllFileNamesDuring: [
  		self repositories do: [ :eachRepository |
  			MCRepositoryGroup default addRepository: eachRepository ].
  		"First, download selected versions"
  		count := 0.
  		selectedVersions := OrderedCollection new.
  		self withProgress: progressString in: self dependencies do: [ :dep | | verName repo |
  			verName := dep versionInfo name.
  			self class extraProgressInfo ifTrue:
+ 				[ ProgressNotification signal: '' extra: ('Downloading {1}' translated format: {verName}) ].
- 				[ ProgressNotification signal: '' extra: 'Downloading ' , verName ].
  			repo := self repositories
  				detect: [ :eachRepository | eachRepository includesVersionNamed: verName ]
+ 				ifNone: 	[ self logError: ('Version {1} not found in any repository' translated format: {verName}).
+ 					self logError: 'Aborting' translated.
- 				ifNone: 	[ self logError: 'Version ' , verName , ' not found in any repository'.
- 					self logError: 'Aborting'.
  					^ count ].
  			(selectBlock value: dep) ifTrue: [ | version |
  				version := self versionNamed: verName for: dep from: repo.
+ 				version ifNil: [ self logError: ('Could not download version {1} from {2}' translated format: {verName. repo description}).
+ 					self logError: 'Aborting' translated.
- 				version ifNil: [ self logError: 'Could not download version ' , verName , ' from ' , repo description.
- 					self logError: 'Aborting'.
  					^ count ].
  				dep package workingCopy newRepositoryGroupIfDefault. "fix old working copies"
  				dep package workingCopy repositoryGroup addRepository: repo.
  				selectedVersions add: version]].
  		"Then, process only those definitions that moved from one package to another, to avoid order dependence"
  		cleanWorkingCopies := MCWorkingCopy allManagers select:
  			[ :wc | wc modified not and:
  				[ selectedVersions anySatisfy: [ :v | wc package = v package ] ] ].
  		MCReorganizationPreloader preloadMovesBetween: selectedVersions.
  		"Finally, load/merge selected versions"
  		self withProgress: progressString in: selectedVersions do: [ :version |
  			self logUpdate: version package with: version.
  			self class extraProgressInfo ifTrue:
+ 				[ ProgressNotification signal: '' extra: ('Installing {1}' translated format: {version info name}) ].
- 				[ ProgressNotification signal: '' extra: 'Installing ' , version info name ].
  			verBlock value: version.
  			count := count + 1 ].
  		"Clean up packages made dirty by MCReorganizationPreloader"
  		cleanWorkingCopies
  			select: [ :wc | wc modified ]
  			thenDo: [ :wc | wc checkModified ].
  	].
  	^ count!

Item was changed:
  ----- Method: MCConfiguration>>load (in category 'actions') -----
  load
  	^self depsSatisfying: [:dep | dep isCurrent not]
  		versionDo: [:ver | ver load]
+ 		displayingProgress: 'loading packages' translated!
- 		displayingProgress: 'loading packages'
- !

Item was changed:
  ----- Method: MCConfiguration>>merge (in category 'actions') -----
  merge
  	^self depsSatisfying: [:dep | dep isFulfilledByAncestors not]
  		versionDo: [:ver | ver merge]
+ 		displayingProgress: 'merging packages' translated!
- 		displayingProgress: 'merging packages'
- !

Item was changed:
  ----- Method: MCConfiguration>>updateFromRepositoriesWithoutCaching (in category 'updating') -----
  updateFromRepositoriesWithoutCaching
  
  	| oldNames newNames sortedNames newDeps |
  	oldNames := self dependencies collect: [:dep | dep versionInfo versionName].
  	newNames := Dictionary new.
  	self repositories
  		do: [:repo | 
+ 			ProgressNotification signal: '' extra: ('Checking {1}' translated format: {repo description}).
- 			ProgressNotification signal: '' extra: 'Checking ', repo description.
  			(repo possiblyNewerVersionsOfAnyOf: oldNames)
  				do: [:newName | newNames at: newName put: repo]]
+ 		displayingProgress: 'Searching new versions' translated.
- 		displayingProgress: 'Searching new versions'.
  
  	sortedNames := newNames keys asArray sort:
  		[:a :b | a versionNumber > b versionNumber].
  
  	newDeps := OrderedCollection new: self dependencies size.
  	self dependencies
  		do: [:dep |
  			newDeps add: (sortedNames
  				detect: [:each | each packageAndBranchName = dep packageAndBranchName]
  				ifFound: [ :newName |
  					| repo |
  					repo := newNames at: newName.
  					(self versionInfoNamed: newName for: dep from: repo)
  						ifNil: [ dep ]
  						ifNotNil: [ :info |
  							MCVersionDependency package: dep package info: info ] ]
  				ifNone: [ dep ]) ]
  		displayingProgress: 'Downloading new versions ...' translated.
  
+ 	self dependencies: newDeps.!
- 	self dependencies: newDeps.
- !

Item was changed:
  ----- Method: MCConfiguration>>updateFromRepositoriesWithoutCaching: (in category 'updating') -----
  updateFromRepositoriesWithoutCaching: packageIndex
  
  	| oldNames newNames sortedNames newDeps dep |
  	dep := dependencies at: packageIndex.
  	oldNames := {dep versionInfo versionName}.
  	newNames := Dictionary new.
  	self repositories
  		do: [:repo | 
+ 			ProgressNotification signal: '' extra: ('Checking {1}' translated format: {repo description}).
- 			ProgressNotification signal: '' extra: 'Checking ', repo description.
  			(repo possiblyNewerVersionsOfAnyOf: oldNames)
  				do: [:newName | newNames at: newName put: repo]]
+ 		displayingProgress: 'Searching new versions' translated.
- 		displayingProgress: 'Searching new versions'.
  
  	sortedNames := newNames keys asArray sort:
  		[:a :b | a versionNumber > b versionNumber].
  
  	newDeps := self dependencies copy.
  	newDeps at: packageIndex put: (
  		sortedNames
  				detect: [:each | each packageAndBranchName = dep packageAndBranchName]
  				ifFound: [ :newName |
  					| repo |
  					repo := newNames at: newName.
  					(self versionInfoNamed: newName for: dep from: repo)
  						ifNil: [ dep ]
  						ifNotNil: [ :info |
  							MCVersionDependency package: dep package info: info ] ]
  				ifNone: [ dep ]).
  
+ 	self dependencies: newDeps.!
- 	self dependencies: newDeps.
- !

Item was changed:
  ----- Method: MCConfiguration>>upgrade (in category 'actions') -----
  upgrade
  	^self depsSatisfying:
  			[:dep | dep isFulfilledByAncestors not]
  		versionDo:
  			[:ver | 
  			(self class upgradeIsMerge and: [ver shouldMerge])
  				ifFalse: [ver load]
  				ifTrue:
  					[[ver merge]
  						on: MCNoChangesException
  						do: [:req| req resume ]
  						on: MCMergeResolutionRequest
  						do: [:request |
  							request merger conflicts isEmpty
  								ifTrue: [request resume: true]
  								ifFalse: [request pass]]
  						on: Deprecation
  						do: [:req| req resume ]]]
+ 		displayingProgress: 'upgrading packages' translated!
- 		displayingProgress: 'upgrading packages'!

Item was changed:
  ----- Method: MCConfiguration>>versionNamed:for:from: (in category 'private') -----
  versionNamed: aMCVersionName for: aDependency from: repo
  
  	| baseName fileName ver |
  	(repo filterFileNames: repo cachedFileNames forVersionNamed: aMCVersionName) ifNotEmptyDo: [:cachedNames |
  		fileName := cachedNames anyOne.
  		self class extraProgressInfo
+ 			ifTrue: [ProgressNotification signal: '' extra: ('Using cached {1}' translated format: {fileName})].
- 			ifTrue:[ProgressNotification signal: '' extra: 'Using cached ', fileName].
  		ver := repo versionNamed: fileName].
  	ver ifNil: [
  		baseName := self diffBaseFor: aDependency.
  		(baseName notNil and: [baseName ~= aMCVersionName and: [repo includesVersionNamed: baseName]]) ifTrue: [
  			fileName := (MCDiffyVersion nameForVer: aMCVersionName base: baseName), '.mcd'.
  			self class extraProgressInfo
+ 				ifTrue: [ProgressNotification signal: '' extra: ('Downloading {1}' translated format: {fileName})].
- 				ifTrue:[ProgressNotification signal: '' extra: 'Downloading ', fileName].
  			ver := [repo versionNamed: fileName] ifError: []]].
  	ver ifNil: [
  		fileName := aMCVersionName versionName, '.mcz'.
  		self class extraProgressInfo
+ 			ifTrue: [ProgressNotification signal: '' extra: ('Downloading {1}' translated format: {fileName})].
- 			ifTrue:[ProgressNotification signal: '' extra: 'Downloading ', fileName].
  		ver := repo versionNamed: fileName].
  	^ver!

Item was changed:
  ----- Method: MCConfigurationBrowser>>addDependency (in category 'dependencies') -----
  addDependency
  	(self pickWorkingCopiesSatisfying: [:each | (self includesPackage: each package) not])
  		do: [:wc |
  			wc ancestors isEmpty
+ 				ifTrue: [self inform: ('You must save {1} first!!
+ Skipping this package' translated format: {wc packageName})]
- 				ifTrue: [self inform: 'You must save ', wc packageName, ' first!!
- Skipping this package']
  				ifFalse: [
  					self dependencies add: (MCVersionDependency
  						package: wc package
  						info: wc ancestors first)]].
  	self changed: #dependencyList; changed: #description!

Item was changed:
  ----- Method: MCConfigurationBrowser>>addRepository (in category 'repositories') -----
  addRepository
  	(self pickRepositorySatisfying:
  		[ : ea | (self repositories includes: ea) not ]) ifNotNil:
+ 		[ : repo | repo class supportsConfigurations ifFalse: [ ^ self inform: 'Not all of these repositories support MCConfigurations.' translated ].
- 		[ : repo | repo class supportsConfigurations ifFalse: [ ^ self inform: 'Not all of these repositories support MCConfigurations.' ].
  		self repositories add: repo.
  		self changed: #repositoryList ]!

Item was changed:
  ----- Method: MCConfigurationBrowser>>changedList (in category 'selection') -----
  changedList
  	self dependencyIndex > 0 ifTrue: [^self changed: #dependencyList].
  	self repositoryIndex > 0 ifTrue: [^self changed: #repositoryList].
+ 	self error: 'nothing selected' translated!
- 	self error: 'nothing selected'!

Item was changed:
  ----- Method: MCConfigurationBrowser>>checkMissing (in category 'dependencies') -----
  checkMissing
  	| missing |
  	missing := (self dependencies collect:
  		[ : ea | ea versionInfo name ]) asSet.
  	self repositories do:
  		[ : eachRepository | eachRepository cacheAllFileNamesDuring:
  			[ missing copy do:
  				[ : eachVersionName | (eachRepository includesVersionNamed: eachVersionName) ifTrue: [ missing remove: eachVersionName ] ] ] ].
  	^ missing isEmpty or:
  		[ self selectDependency: missing anyOne.
  		self confirm:
  			(String streamContents:
  				[ : strm | strm
+ 					 nextPutAll: 'No repository found for' translated ;
- 					 nextPutAll: 'No repository found for' ;
  					 cr.
  				missing do:
  					[ : r | strm
  						 nextPutAll: r ;
  						 cr ].
+ 				strm nextPutAll: 'Do you still want to store?' translated ]) ]!
- 				strm nextPutAll: 'Do you still want to store?' ]) ]!

Item was changed:
  ----- Method: MCConfigurationBrowser>>checkModified (in category 'dependencies') -----
  checkModified
  	| modified |
  	modified := self dependencies select: [:dep |
  		dep isFulfilled and: [dep package workingCopy modified]].
  	
  	^modified isEmpty or: [
  		self selectDependency: modified anyOne.
  		self confirm: (String streamContents: [:strm |
+ 			strm nextPutAll: 'These packages are modified:' translated; cr.
- 			strm nextPutAll: 'These packages are modified:'; cr.
  			modified do: [:dep | strm nextPutAll: dep package name; cr].
+ 			strm nextPutAll: 'Do you still want to store?' translated])]!
- 			strm nextPutAll: 'Do you still want to store?'])]
- 	!

Item was changed:
  ----- Method: MCConfigurationBrowser>>checkRepositories (in category 'repositories') -----
  checkRepositories
  	| bad |
  	bad := self repositories reject: [:repo | repo class supportsConfigurations ].
  	^bad isEmpty or: [
  		self selectRepository: bad first.
  		self inform: (String streamContents: [:strm |
+ 			strm nextPutAll: 'Please remove these repositories:' translated; cr.
- 			strm nextPutAll: 'Please remove these repositories:'; cr.
  			bad do: [:r | strm nextPutAll: r description; cr].
+ 			strm nextPutAll: '(only HTTP repositories are supported)' translated]).
- 			strm nextPutAll: '(only HTTP repositories are supported)']).
  		false].
  !

Item was changed:
  ----- Method: MCConfigurationBrowser>>checkRepositoryTemplates (in category 'repositories') -----
  checkRepositoryTemplates
  	"unused for now - we only do HTTP"
  	| bad |
  	bad := self repositories select: [:repo | repo creationTemplate isNil].
  	^bad isEmpty or: [
  		self selectRepository: bad first.
  		self inform: (String streamContents: [:strm |
+ 			strm nextPutAll: 'Creation template missing for' translated; cr.
- 			strm nextPutAll: 'Creation template missing for'; cr.
  			bad do: [:r | strm nextPutAll: r description; cr].
+ 			strm nextPutAll: 'Please fill in the details first!!' translated]).
- 			strm nextPutAll: 'Please fill in the details first!!']).
  		false].
  !

Item was changed:
  ----- Method: MCConfigurationBrowser>>completeStoreAction (in category 'actions') -----
  completeStoreAction
  	"The store method will arrange for this to be called after the user has entered
  	a comment for the configuration version being stored."
  	self activeEditWindow: nil. "Close the editor window"
  	self pickRepository
  		ifNotNil: [:repo | 
  			configuration authorInitials: Utilities authorInitials.
  			configuration timeStamp: (DateAndTime fromSeconds: DateAndTime now asSeconds) printString.
  			configuration id: UUID new asString.
  			(repo includesVersionNamed: configuration name)
  				ifTrue: [self notify: ('The configuration does already exist in the repository you specified. If you proceed, it will be overwritten.\\Repository: {1}\Configuration: {2}\\Do you want to proceed anyway?' translated withCRs format: { repo description. configuration name })].
  			repo storeVersion: configuration.
+ 			self inform: ('Saved {1}' translated format: {configuration name})]!
- 			self inform: 'Saved ', configuration name]!

Item was changed:
  ----- Method: MCConfigurationBrowser>>description (in category 'description') -----
  description
  	self selectedDependency ifNotNil:
  		[:dep |
+ 		^ ('Package: {1}\{2}' withCRs translated format: {dep package name. dep versionInfo summary}) asText].
- 		^ ('Package: ', dep package name, String cr, dep versionInfo summary) asText].
  	self selectedRepository ifNotNil:
  		[:repo |
  		^repo creationTemplate
  			ifNotNil: [repo creationTemplate asText]
  			ifNil: [repo asCreationTemplate asText addAttribute: TextColor red]].
+ 	^'A configuration is a set of particular versions of packages.  These can be used to manage multiple dependencies amongst packages when an update requires changes to multiple packages.  One stores the current configuration and then modifies the various packages needing modification.  On load, the image will be updated to at least the versions in the current configuration, hence providing the support needed to load the new packages.\\To create a new configuration first load the most up-to-date configuration in your repository (e.g., {1}), open that repository in the Monticello browser, scroll down to the "update" package, select the first entry in the list on the right hand side and click Browse, which will open the configuration in a new MCConfigurationBrowser.  Then in the new MCConfigurationBrowser click Update, and choose "update all from image" from the pop-up menu.  Click Store to save back to the repository.  If required, one can add repositories to the browser to store the 
 configuration in a different repository.' withCRs translated format: {MCHttpRepository trunkUrlString}!
- 	^('A configuration is a set of particular versions of packages.  These can be used to manage multiple dependencies amongst packages when an update requires changes to multiple packages.  One stores the current configuration and then modifies the various packages needing modification.  On load, the image will be updated to at least the versions in the current configuration, hence providing the support needed to load the new packages.\\To create a new configuration first load the most up-to-date configuration in your repository (e.g.',  MCHttpRepository trunkUrlString, '), open that repository in the Monticello browser, scroll down to the "update" package, select the first entry in the list on the right hand side and click Browse, which will open the configuration in a new MCConfigurationBrowser.  Then in the new MCConfigurationBrowser click Update, and choose "update all from image" from the pop-up menu.  Click Store to save back to the repository.  If required, one can add reposit
 ories to the browser to store the configuration in a different repository.') withCRs!

Item was changed:
  ----- Method: MCConfigurationBrowser>>description: (in category 'description') -----
  description: aText
  
  	self selectedRepository ifNotNil: [:repo | 
  		| new | 
  		new := MCRepository readFrom: aText asString.
  		(new class = repo class 
  			and: [new description = repo description])
  				ifTrue: [
  					repo creationTemplate: aText asString.
  					self changed: #description]
  				ifFalse: [
+ 					self inform: 'This does not match the previous definition!!' translated
- 					self inform: 'This does not match the previous definition!!'
  				]
  	].
  
  !

Item was changed:
  ----- Method: MCConfigurationBrowser>>enterVersionCommentAndCompleteWith:nameForRestore: (in category 'morphic ui') -----
  enterVersionCommentAndCompleteWith: aConfigBrowser nameForRestore: originalName
  	"Open an editor for comment entry. When text is accepted from the editor, ask
  	if editing is done. If complete, then proceed to save the MCConfiguration. If cancelled,
  	close the edit window and do nothing further. Otherwise leave the edit window open
  	to allow further edits before proceeding to save the configuration."
  	| editWindow |
+ 	editWindow := Project uiManager
- 	editWindow := UIManager default
  		edit: configuration comment
+ 		label: ('Enter or edit a comment for {1}' translated format: {configuration name})
- 		label: 'Enter or edit a comment for ', configuration name
  		accept: [:aText | | editingComplete |
  			editingComplete := UIManager default
  				confirm: 'Comment accepted' translated
+ 				title: ('Comment for {1}' translated format: {configuration name})
- 				title: 'Comment for ' translated, configuration name
  				trueChoice: 'Proceed to save configuration' translated
  				falseChoice: 'Continue editing comment' translated.
  			editingComplete
  				ifNil: [ "cancel button pressed"
  					configuration name: originalName. "cancelling, undo the changed name"
  					Project current
  					addDeferredUIMessage: [aConfigBrowser activeEditWindow ifNotNil: [ :win | win delete ]]] 
  				ifNotNil: [ editingComplete
  					ifTrue: [configuration comment: aText asString.
  						Project current
  							addDeferredUIMessage: [aConfigBrowser completeStoreAction]]
  					ifFalse: [ "edit window remains open" ]]].
+ 	aConfigBrowser activeEditWindow: editWindow.!
- 	aConfigBrowser activeEditWindow: editWindow.
- !

Item was changed:
  ----- Method: MCConfigurationBrowser>>index: (in category 'selection') -----
  index: anInteger
  	self dependencyIndex > 0 ifTrue: [^self dependencyIndex: anInteger].
  	self repositoryIndex > 0 ifTrue: [^self repositoryIndex: anInteger].
+ 	anInteger > 0 ifTrue: [self error: 'cannot select' translated]!
- 	anInteger > 0 ifTrue: [self error: 'cannot select']!

Item was changed:
  ----- Method: MCConfigurationBrowser>>pickName (in category 'morphic ui') -----
  pickName
  	| name |
+ 	name := Project uiManager
+ 		request: ('Name ({1} will be appended):' translated format: {'.' , self configuration writerClass extension})
- 	name := UIManager default
- 		request: 'Name (.', self configuration writerClass extension, ' will be appended):'
  		initialAnswer: self configuration suggestedNameOfNextVersion.
  	^ name isEmpty ifFalse: [name]!

Item was changed:
  ----- Method: MCConfigurationBrowser>>pickRepositorySatisfying: (in category 'morphic ui') -----
  pickRepositorySatisfying: aBlock
  	| index list |
  	list := MCRepositoryGroup default repositories select: aBlock.
+ 	index := Project uiManager chooseFrom: (list collect: [:ea | ea description])
+ 		title: 'Repository:' translated.
- 	index := UIManager default chooseFrom: (list collect: [:ea | ea description])
- 		title: 'Repository:'.
  	^ index = 0 ifFalse: [list at: index]!

Item was changed:
  ----- Method: MCConfigurationBrowser>>pickWorkingCopiesSatisfying: (in category 'morphic ui') -----
  pickWorkingCopiesSatisfying: aBlock
  	| copies item |
  	copies := (MCWorkingCopy allManagers select: aBlock)
  		sort: [:a :b | a packageName <= b packageName].
+ 	item := Project uiManager chooseFrom: #('match ...'),(copies collect: [:ea | ea packageName]) lines: #(1) title: 'Package:' translated.
- 	item := UIManager default chooseFrom: #('match ...'),(copies collect: [:ea | ea packageName]) lines: #(1) title: 'Package:'.
  	item = 1 ifTrue: [
  		| pattern |
+ 		pattern := Project uiManager request: 'Packages matching:' translated initialAnswer: '*'.
- 		pattern := UIManager default request: 'Packages matching:' initialAnswer: '*'.
  		^pattern isEmptyOrNil
  			ifTrue: [#()]
  			ifFalse: [
  				(pattern includes: $*) ifFalse: [pattern := '*', pattern, '*'].
  				copies select: [:ea | pattern match: ea packageName]]
  	].
  	^ item = 0
  		ifTrue: [#()]
  		ifFalse: [{copies at: item - 1}]!

Item was changed:
  ----- Method: MCMcmUpdater class>>defaultUpdateURL (in category 'preferences') -----
  defaultUpdateURL
  	"The default update repository URL"
  
  	<preference: 'Update URL'
  		category: 'updates'
  		description: 'The repository URL for loading updates'
  		type: #String>
  
  	^ DefaultUpdateURL ifNil: [
  		self notify: 'There is no update URL configured. Proceed to use Squeak''s Trunk repository.' translated.
+ 		MCHttpRepository trunkUrlString]!
- 		'http://source.squeak.org/trunk']!

Item was changed:
  ----- Method: MCMcmUpdater>>logUpdateOf:previousUpdateLevel:interactive: (in category 'updating') -----
  logUpdateOf: config previousUpdateLevel: previousUpdateLevel interactive: interactive
  	MCMcmUpdater default == self
  		ifTrue: [
  			config setSystemVersion.
  			interactive ifTrue: [
  				self inform: (self updateMessageFor: previousUpdateLevel)].
  			Transcript cr;
+ 				show: ('==========  Update of {1} completed:  ' translated format: {self repositoryName});
- 				show: '==========  Update of ' translated, self repositoryName, ' completed:  ' translated;
  				show: previousUpdateLevel;
  				show: ' -> ' ;
  				show: SystemVersion current highestUpdate;
  				show: ' =========='; cr ]
  		ifFalse: [
  			interactive
+ 				ifTrue: [ self inform: ('Update of {1} completed.' translated format: {self repositoryName}) ].
+ 			Transcript cr; show: ('==========  Update of {1} completed. ==========' translated format: {self repositoryName}); cr ]
- 				ifTrue: [ self inform: 'Update of ', self repositoryName, ' completed.' ].
- 			Transcript cr; show: '==========  Update of ' translated, self repositoryName, ' completed. ==========' translated; cr ]
  
  	!

Item was changed:
  ----- Method: MCMcmUpdater>>updateFromRepository (in category 'updating') -----
  updateFromRepository
  
  	| config repo |
  	repo := self getRepositoryFromRepositoryGroup.
  	repo cacheAllFileNamesDuring: [ | updateList |
  		updateList := self updateListFor: repo.
  		"Proceed only if there are updates available at all."
  		updateList ifNotEmpty: [
  			updateList := self refreshUpdateMapFor: repo with: updateList.
  			"Now process each update file. Check if we have all dependencies and if not,
  			load the entire configuration (this is mostly to skip older updates quickly)"
  			updateList do:[:assoc|
+ 				ProgressNotification signal: '' extra: ('Processing {1}' translated format: {assoc value}).
- 				ProgressNotification signal: '' extra: 'Processing ', assoc value.
  				config := repo versionNamed: assoc value.
  				self updateFromConfig: config.
  				self lastUpdateMap at: repo description put: assoc key.
+ 			] displayingProgress: 'Processing configurations' translated.
- 			] displayingProgress: 'Processing configurations'.
  			"We've loaded all the provided update configurations.
  			Use the latest configuration to update all the remaining packages."
  			(self useLatestPackagesFrom: repo) ifTrue: [
  				config updateFromRepositories.
  				config upgrade].
  		]].
  	^ config
  !

Item was changed:
  ----- Method: MCMcmUpdater>>updateFromRepository:upTo: (in category 'updating') -----
  updateFromRepository: repository upTo: versionNumber
  
  	| config |
+ 	config := nil.
  	repository cacheAllFileNamesDuring: [ | updateList |
  		updateList := self updateListFor: repository.
  		"Proceed only if there are updates available at all."
  		updateList ifNotEmpty: [
  			updateList := self refreshUpdateMapFor: repository with: updateList.
  			"Now process each update file. Check if we have all dependencies and if not,
  			load the entire configuration (this is mostly to skip older updates quickly)"
  			updateList do:[:assoc|
  				assoc key > versionNumber ifTrue: [^config].
+ 				ProgressNotification signal: '' extra: ('Processing ' translated format: {assoc value}).
- 				ProgressNotification signal: '' extra: 'Processing ', assoc value.
  				config := repository versionNamed: assoc value.
  				self updateFromConfig: config.
  				self lastUpdateMap at: repository description put: assoc key.
+ 			] displayingProgress: 'Processing configurations' translated.
- 			] displayingProgress: 'Processing configurations'.
  		]].
  	^config
  !

Item was changed:
  ----- Method: MCMcmUpdater>>updateListFor: (in category 'private') -----
  updateListFor: repo
  
  	| updateList allNames minVersion |
  	updateList := OrderedCollection new.
  	minVersion := self lastUpdateMap at: repo description ifAbsent: [0].
  	"Find all the update-*.mcm files"
+ 	allNames := ('Checking {1}' translated format: {repo description})
- 	allNames := 'Checking ', repo description
  		displayProgressFrom: 0 to: 1 during: [:bar| 
  			bar value: 0.
  			repo allFileNamesOrCache ].
  	allNames do: [:fileName | | version |
  		((fileName endsWith: '.mcm')
  			and: [fileName packageAndBranchName = self updateMapName
  				and: [(version := fileName versionNumber) >= minVersion]]) 
  					ifTrue: [updateList add: version -> fileName]].
  	^updateList sort!



More information about the Squeak-dev mailing list