[squeak-dev] The Inbox: MonticelloConfigurations-dtl.131.mcz

commits at source.squeak.org commits at source.squeak.org
Mon May 4 20:12:39 UTC 2015


David T. Lewis uploaded a new version of MonticelloConfigurations to project The Inbox:
http://source.squeak.org/inbox/MonticelloConfigurations-dtl.131.mcz

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

Name: MonticelloConfigurations-dtl.131
Author: dtl
Time: 4 May 2015, 4:12:33.318 pm
UUID: 2e9a311b-a484-4f84-af4e-96dd6d373bfe
Ancestors: MonticelloConfigurations-mt.130

Let MCMcmUpdater be instance based.

The default system updater is MCMcmUpdater default.

Updaters are associated with repositories ('http://source.squeak.org/trunk'), and are kept in a registry (MCMcmUpdater updaters) keyed by repository URL.

Each updater has its own updateMapName (such as 'update' or 'update.spur') and maintains its own lastUpdateMap.

System preferences apply to the default updater.

A SqueakMap package head stream can specify its update map name independent of the Squeak trunk update stream preference, for example:

  "MCMcmUpdater updateMapName: 'update.oscog' repository: 'http://source.squeak.org/VMMaker'

=============== Diff against MonticelloConfigurations-mt.130 ===============

Item was changed:
  Object subclass: #MCMcmUpdater
+ 	instanceVariableNames: 'updateMapName lastUpdateMap'
+ 	classVariableNames: 'DefaultUpdateURL LastUpdateMap SkipPackages UpdateFromServerAtStartup UpdateMapName UpdateMissingPackages Updaters'
- 	instanceVariableNames: ''
- 	classVariableNames: 'DefaultUpdateURL LastUpdateMap SkipPackages UpdateFromServerAtStartup UpdateMapName UpdateMissingPackages'
  	poolDictionaries: ''
  	category: 'MonticelloConfigurations'!
  
+ !MCMcmUpdater commentStamp: 'dtl 5/4/2015 16:03' prior: 0!
- !MCMcmUpdater commentStamp: 'cbc 8/26/2010 16:42' prior: 0!
  MCMcmUpdater provides utility methods for updating Monticello packages from Monticello configurations.
  
  When Monticello configurations are stored in a repository (or repositories), MCMcmUpdater acts as an update stream. It first ensures that each configuration map has been loaded in sequence, then updates the last configuration map to the most recent version for each specified package, and finally loads these versions to produce a fully updated configuration.
  
  Currently if a set of packages are unloaded from the image, using this class to reload them may cause problems, depending on what dependencies those classes have.  Success is not assured.  Removing packages via SmalltalkImage>>unloadAllKnownPackages will be successful, it flags the packages removed so that they are not loaded by this utility.
  
  If you wish to not have MCMcmUpdater update packages, there are two ways to handle this:
  
  1) To have MCMcmUpdater not update any packages not currently in the image set the UpdateMissingPackages preference to false:
  		MCMcmUpdater updateMissingPackages: false
  	Note that any new packages added to the repositories will not be picked up when this is turned off.
  2) To have MCMcmUpdater not update a specific package, evaluate
  		MCMcmUpdater disableUpdatesOfPackage: <packageName>
  
  Class Variables definitions:
  
  DefaultUpdateURL - String: the URL that will be checked by default for updates.  This would be set for a common standard location to check.
  
+ Updaters - A dictionary of MCMcmUpdater instances keyed by repository URL.
- LastUpdateMap - Dictionary of Integer: version number of the last loaded update map per repository.  Keeps track of the last configuration map, so that the utility will not have to run through the full history in the repositories each time you ask to update.
  
  SkipPackages - Set of Strings: names of packages to not update in MCMcmUpdater (empty by default).
  
  UpdateMissingPackages - Boolean: if true (default), new packages in the update config map will be loaded unless they are in SkipPackages.  If false, packages not currently loaded in the image will not be loaded by MCMcmUpdater.  (This can be dangerous if packages are split - use at your own risk).
+ 
+ Instance Variables:
+ 
+ updateMapName - Base name of the files used for this updater, typically a name such as 'update' or 'update.spur'.
+ 
+ lastUpdateMap - Dictionary of Integer: version number of the last loaded update map per repository.  Keeps track of the last configuration map, so that the utility will not have to run through the full history in the repositories each time you ask to update.
  !

Item was added:
+ ----- Method: MCMcmUpdater class>>default (in category 'instance creation') -----
+ default
+ 	"The default instance for system updates. Uses a default update map
+ 	name that may be set as a preference to enable a specific update stream
+ 	for a repository."
+ 
+ 	^ self updaters
+ 		at: self defaultUpdateURL
+ 		ifAbsentPut: [self updateMapName: self updateMapName]!

Item was changed:
  ----- Method: MCMcmUpdater class>>initialize (in category 'class initialization') -----
  initialize
  	"MCMcmUpdater initialize"
  	LastUpdateMap ifNil:[
  		LastUpdateMap := Dictionary new.
  	].
  	DefaultUpdateURL ifNil:[
  		DefaultUpdateURL := MCHttpRepository trunkUrlString.
+ 	].
+ 	Updaters := nil.
+ 	self flag: #FIXME.
+ 		"The next line is to faciliate updating from class-side methods to instance based.
+ 		Building a new default update map is very time consuming, so do not do it.
+ 		Delete this after the transition is complete. Also delete class var LastUpdateMap
+ 		and its initialization above. -dtl May 2015"
+ 	LastUpdateMap ifNotNil: [ self default lastUpdateMap: LastUpdateMap ]
+ !
- 	].!

Item was removed:
- ----- Method: MCMcmUpdater class>>refreshUpdateMapFor:with: (in category 'updating') -----
- refreshUpdateMapFor: r with: updateList
- 	"Update the LastUpdateMap and answer a possibly reduced updateList"
- 
- 	| config |
- 	(LastUpdateMap at: r description ifAbsent: [0]) = 0 ifTrue: [
- 		"No update has ever been loaded from this repo. If no package is
- 		present in the image either, we can skip right to the latest config"
- 		config := r versionNamed: updateList last value.
- 		(config dependencies anySatisfy: [:dep| dep package hasWorkingCopy])
- 			ifFalse: [ (self useLatestPackagesFrom: r)
- 				ifTrue: [LastUpdateMap at: r description put: updateList last key.
- 					 ^ #()]
- 				ifFalse: [ ^ updateList last: 1]]].
- 	^ updateList
- !

Item was changed:
+ ----- Method: MCMcmUpdater class>>skipPackages (in category 'preferences') -----
- ----- Method: MCMcmUpdater class>>skipPackages (in category 'private') -----
  skipPackages
  	^SkipPackages ifNil: [SkipPackages := Set new]!

Item was removed:
- ----- Method: MCMcmUpdater class>>updateFromConfig: (in category 'updating') -----
- updateFromConfig: config
- 
- 	"Skip packages that were specifically unloaded"
- 	config dependencies: (config dependencies 
- 		reject: [:dep| self skipPackages includes: dep package name]).
- 	self updateMissingPackages ifFalse:[
- 		"Skip packages that are not in the image"
- 		config dependencies: (config dependencies 
- 			select: [:dep| dep package hasWorkingCopy])].
- 	(config dependencies allSatisfy:[:dep| dep isFulfilled]) 
- 		ifFalse:[config upgrade].
- !

Item was removed:
- ----- Method: MCMcmUpdater class>>updateFromDefaultRepository (in category 'updating') -----
- updateFromDefaultRepository
- 	"Update from the default repository only"
- 	^self updateFromRepositories: {self defaultUpdateURL}!

Item was changed:
  ----- Method: MCMcmUpdater class>>updateFromRepositories: (in category 'updating') -----
  updateFromRepositories: repositoryUrls
  	"MCMcmUpdater updateFromRepositories: #(
  		'http://squeaksource.com/MCUpdateTest'
  	)"
  
+ 	^ self default updateFromRepositories: repositoryUrls!
- 	| repos config |
- 	MCConfiguration upgradeIsMerge: true.
- 	LastUpdateMap ifNil:[LastUpdateMap := Dictionary new].
- 	"The list of repositories to consult in order"
- 	repos := repositoryUrls collect:[:url| 
- 		MCRepositoryGroup default repositories 
- 			detect:[:r| r description = url]
- 			ifNone:[ | r |
- 				r := MCHttpRepository location: url user: '' password: ''.
- 				MCRepositoryGroup default addRepository: r.
- 				r]].
- 
- 	"The list of updates-author.version.mcm sorted by version"
- 	repos do:[ :r | config := self updateFromRepository: r ].
- 	^config!

Item was added:
+ ----- Method: MCMcmUpdater class>>updateFromRepositories:using:baseName: (in category 'updating') -----
+ updateFromRepositories: repositoryUrls using: updaterUrlKey baseName: baseName
+ 	"Update all repositoryUrls using an MCMcmUpdater identified by updaterUrlKey, and
+ 	using update map baseName"
+ 
+ 	^ (self updateMapName: baseName repository: updaterUrlKey)
+ 		updateFromRepositories: repositoryUrls!

Item was removed:
- ----- Method: MCMcmUpdater class>>updateFromRepository: (in category 'updating') -----
- updateFromRepository: repository
- 
- 	| config |
- 	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|
- 				ProgressNotification signal: '' extra: 'Processing ', assoc value.
- 				config := repository versionNamed: assoc value.
- 				self updateFromConfig: config.
- 				LastUpdateMap at: repository description put: assoc key.
- 			] displayingProgress: 'Processing configurations'.
- 			"We've loaded all the provided update configurations.
- 			Use the latest configuration to update all the remaining packages."
- 			(self useLatestPackagesFrom: repository) ifTrue: [
- 				config updateFromRepositories.
- 				config upgrade].
- 		]].
- 	^ config
- !

Item was changed:
  ----- Method: MCMcmUpdater class>>updateFromServer (in category 'updating') -----
  updateFromServer
  	"Update the image by loading all pending updates from the server."
+ 
+ 	^self default updateFromServer
+ !
- 	| config |
- 	"Flush all caches. If a previous download failed this is often helpful"
- 	MCFileBasedRepository flushAllCaches.
- 	config := MCMcmUpdater updateFromDefaultRepository.
- 	config ifNil: [^self inform: 'Unable to retrieve updates from remote repository.' translated].
- 	config setSystemVersion.
- 	self inform: ('Update completed.
- Current update number: ' translated, SystemVersion current highestUpdate).!

Item was removed:
- ----- Method: MCMcmUpdater class>>updateListFor: (in category 'private') -----
- updateListFor: repo
- 
- 	| updateList allNames minVersion |
- 	updateList := OrderedCollection new.
- 	minVersion := LastUpdateMap at: repo description ifAbsent: [0].
- 	"Find all the update-*.mcm files"
- 	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!

Item was changed:
+ ----- Method: MCMcmUpdater class>>updateMapName: (in category 'instance creation') -----
+ updateMapName: baseName
+ 	"Answer a new instance with a base update name baseName such as
+ 	'update' or 'update.oscog' "
+ 
+ 	^ self new updateMapName: baseName!
- ----- Method: MCMcmUpdater class>>updateMapName: (in category 'preferences') -----
- updateMapName: aString
- 	"Name for update map, without version info"
- 	UpdateMapName := aString!

Item was added:
+ ----- Method: MCMcmUpdater class>>updateMapName:repository: (in category 'instance creation') -----
+ updateMapName: baseName repository: url
+ 	"Answer an instance for the given repository URL with a base update name
+ 	baseName. The instance will be updated in the Updaters dictionary if baseName
+ 	has changed."
+ 
+ 	| updater |
+ 	updater := self updaters at: url ifAbsentPut: [ self updateMapName: baseName ].
+ 	updater updateMapName = baseName
+ 		ifFalse: [ ^ self updaters at: url put: (self updateMapName: baseName )].
+ 	^ updater
+ !

Item was added:
+ ----- Method: MCMcmUpdater class>>updateUsing:baseName: (in category 'updating') -----
+ updateUsing: updaterUrlKey baseName: baseName
+ 	"Update using an MCMcmUpdater identified by updaterUrlKey, and using
+ 	update map baseName"
+ 
+ 	^ (self updateMapName: baseName repository: updaterUrlKey) updateFromServer
+ !

Item was added:
+ ----- Method: MCMcmUpdater class>>updaters (in category 'accessing') -----
+ updaters
+ 	"A dictionary of updaters, including the system default, indexed by repository URL"
+ 
+ 	^ Updaters ifNil: [ Updaters := Dictionary new ]!

Item was removed:
- ----- Method: MCMcmUpdater class>>useLatestPackagesFrom: (in category 'private') -----
- useLatestPackagesFrom: repo
- 	"for overriding on a per repository basis"
- 	^true!

Item was added:
+ ----- Method: MCMcmUpdater>>lastUpdateMap (in category 'accessing') -----
+ lastUpdateMap
+ 
+ 	^ lastUpdateMap ifNil: [ lastUpdateMap := Dictionary new ]
+ !

Item was added:
+ ----- Method: MCMcmUpdater>>lastUpdateMap: (in category 'accessing') -----
+ lastUpdateMap: aDictionary
+ 
+ 	lastUpdateMap := aDictionary
+ !

Item was added:
+ ----- Method: MCMcmUpdater>>refreshUpdateMapFor:with: (in category 'updating') -----
+ refreshUpdateMapFor: r with: updateList
+ 	"Update the lastUpdateMap and answer a possibly reduced updateList"
+ 
+ 	| config |
+ 	(lastUpdateMap at: r description ifAbsent: [0]) = 0 ifTrue: [
+ 		"No update has ever been loaded from this repo. If no package is
+ 		present in the image either, we can skip right to the latest config"
+ 		config := r versionNamed: updateList last value.
+ 		(config dependencies anySatisfy: [:dep| dep package hasWorkingCopy])
+ 			ifFalse: [ (self useLatestPackagesFrom: r)
+ 				ifTrue: [lastUpdateMap at: r description put: updateList last key.
+ 					 ^ #()]
+ 				ifFalse: [ ^ updateList last: 1]]].
+ 	^ updateList
+ !

Item was added:
+ ----- Method: MCMcmUpdater>>skipPackages (in category 'private') -----
+ skipPackages
+ 	^SkipPackages ifNil: [SkipPackages := Set new]!

Item was added:
+ ----- Method: MCMcmUpdater>>updateFromConfig: (in category 'updating') -----
+ updateFromConfig: config
+ 
+ 	"Skip packages that were specifically unloaded"
+ 	config dependencies: (config dependencies 
+ 		reject: [:dep| self class skipPackages includes: dep package name]).
+ 	self class updateMissingPackages ifFalse:[
+ 		"Skip packages that are not in the image"
+ 		config dependencies: (config dependencies 
+ 			select: [:dep| dep package hasWorkingCopy])].
+ 	(config dependencies allSatisfy:[:dep| dep isFulfilled]) 
+ 		ifFalse:[config upgrade].
+ !

Item was added:
+ ----- Method: MCMcmUpdater>>updateFromDefaultRepository (in category 'updating') -----
+ updateFromDefaultRepository
+ 	"Update from the default repository only"
+ 	^self updateFromRepositories: {self class defaultUpdateURL}!

Item was added:
+ ----- Method: MCMcmUpdater>>updateFromRepositories: (in category 'updating') -----
+ updateFromRepositories: repositoryUrls
+ 	"MCMcmUpdater updateFromRepositories: #(
+ 		'http://squeaksource.com/MCUpdateTest'
+ 	)"
+ 
+ 	| repos config |
+ 	MCConfiguration upgradeIsMerge: true.
+ 	"The list of repositories to consult in order"
+ 	repos := repositoryUrls collect:[:url| 
+ 		MCRepositoryGroup default repositories 
+ 			detect:[:r| r description = url]
+ 			ifNone:[ | r |
+ 				r := MCHttpRepository location: url user: '' password: ''.
+ 				MCRepositoryGroup default addRepository: r.
+ 				r]].
+ 
+ 	"The list of updates-author.version.mcm sorted by version"
+ 	repos do:[ :r | config := self updateFromRepository: r ].
+ 	^config!

Item was added:
+ ----- Method: MCMcmUpdater>>updateFromRepository: (in category 'updating') -----
+ updateFromRepository: repository
+ 
+ 	| config |
+ 	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|
+ 				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'.
+ 			"We've loaded all the provided update configurations.
+ 			Use the latest configuration to update all the remaining packages."
+ 			(self useLatestPackagesFrom: repository) ifTrue: [
+ 				config updateFromRepositories.
+ 				config upgrade].
+ 		]].
+ 	^ config
+ !

Item was added:
+ ----- Method: MCMcmUpdater>>updateFromServer (in category 'updating') -----
+ updateFromServer
+ 	"Update the image by loading all pending updates from the server."
+ 	| config |
+ 	"Flush all caches. If a previous download failed this is often helpful"
+ 	MCFileBasedRepository flushAllCaches.
+ 	config := MCMcmUpdater default updateFromDefaultRepository.
+ 	config ifNil: [^self inform: 'Unable to retrieve updates from remote repository.' translated].
+ 	config setSystemVersion.
+ 	self inform: ('Update completed.
+ Current update number: ' translated, SystemVersion current highestUpdate).!

Item was added:
+ ----- 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 ', 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!

Item was added:
+ ----- Method: MCMcmUpdater>>updateMapName (in category 'accessing') -----
+ updateMapName
+ 	"Name for update map, without version info"
+ 
+ 	^ updateMapName ifNil: [updateMapName := self class updateMapName]!

Item was added:
+ ----- Method: MCMcmUpdater>>updateMapName: (in category 'accessing') -----
+ updateMapName: aString
+ 	"Name for update map, without version info"
+ 	updateMapName := aString!

Item was added:
+ ----- Method: MCMcmUpdater>>useLatestPackagesFrom: (in category 'private') -----
+ useLatestPackagesFrom: repo
+ 	"for overriding on a per repository basis"
+ 	^true!



More information about the Squeak-dev mailing list