[squeak-dev] The Trunk: MonticelloConfigurations-dtl.161.mcz

commits at source.squeak.org commits at source.squeak.org
Sat May 9 15:46:03 UTC 2020


David T. Lewis uploaded a new version of MonticelloConfigurations to project The Trunk:
http://source.squeak.org/trunk/MonticelloConfigurations-dtl.161.mcz

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

Name: MonticelloConfigurations-dtl.161
Author: dtl
Time: 9 May 2020, 10:22:36.276105 am
UUID: 67fc7184-897f-417f-ab90-5f241d35e26b
Ancestors: MonticelloConfigurations-mt.160

A MCConfigurationExtended is a configuration with author initials, timestamp, UUID identifier, comment, and a list of prior versions. Its external storage format is organized for compatibility with MCConfiguration, such that an image wtih support for only MCConfiguration can use configurations saved from a MCConfigurationExtended.

The intended use is to enable documentation of configuration maps, and to allow modifications to a configuration map without loss of version history.

When editing an MCConfiguration, a copyForEdit of the configuration is modfied, leaving the prior configuration in the version history. When saving an edited version, an editor window allows a version comment to be entered for the new configuration. Version history for a saved MCConfiguration is trimmed to a maximum of 10 prior versions to maintain reasonable storage size. Full version history can be reconstructed based on the UUID identifiers.

MCConfigurationBrowser provides a "Versions" button to open an explorer on the version history of a configuration. No other support for browsing version history and comments is provided.

MCConfigurationExtended is fully backward compatible such that saved versions will be rendered as simple MCConfiguration without version history in an image that lacks support for the extended format.

A SqueakSource server must have this update applied before it can render a saved MCConfigurationExtended.

=============== Diff against MonticelloConfigurations-mt.160 ===============

Item was added:
+ ----- Method: MCConfiguration class>>concreteClassFor: (in category 'private') -----
+ concreteClassFor: configArray
+ 	^ (configArray includes: #mcmVersion)
+ 		ifTrue: [MCConfigurationExtended]
+ 		ifFalse: [MCConfiguration].
+ 
+ !

Item was added:
+ ----- Method: MCConfiguration class>>copyWithoutKeyPrefix: (in category 'private') -----
+ copyWithoutKeyPrefix: configArray
+ 	"Tokens in the version history portion of configArray are prefixed with $X to
+ 	prevent them being parsed in the original implementation of MCConfiguration.
+ 	Here we remove the prefixes prior to processing in the current implementation
+ 	with MCConfigurationExtended support. See #contentsOn:keyPrefix: for the
+ 	prefix writer."
+ 	| strm |
+ 	strm := #() writeStream.
+ 	configArray do: [ :token |
+ 		token caseOf: {
+ 				[#Xname ] -> [ strm nextPut: #name] .
+ 				[#Xrepository ] -> [ strm nextPut: #repository] .
+ 				[#Xdependency ] -> [ strm nextPut: #dependency] .
+ 				[#XmcmVersion] -> [ strm nextPut: #mcmVersion] .
+ 				[#Xid] -> [ strm nextPut: #id] .
+ 				[#XauthorInitials ] -> [ strm nextPut: #authorInitials] .
+ 				[#XtimeStamp ] -> [ strm nextPut: #timeStamp] .
+ 				[#Xcomment ] -> [ strm nextPut: #comment]
+ 			}
+ 			otherwise: [ strm nextPut: token]
+ 
+ 
+ 	].
+ 	^ strm contents.
+ 
+ !

Item was changed:
  ----- Method: MCConfiguration class>>fromArray: (in category 'instance creation') -----
  fromArray: anArray
+ 	| array |
+ 	array := self copyWithoutKeyPrefix: anArray.
+ 	^ (self versionsFromStream: array readStream) first.
+ !
- 	| configuration |
- 	configuration := self new.
- 	anArray pairsDo: [:key :value |
- 		key = #repository
- 			ifTrue: [configuration repositories add: (self repositoryFromArray: value)].
- 		key = #dependency
- 			ifTrue: [configuration dependencies add: (self dependencyFromArray: value)].
- 		key = #name
- 			ifTrue: [configuration name: value].
- 	].
- 	^configuration!

Item was added:
+ ----- Method: MCConfiguration class>>nextArrayFrom: (in category 'private') -----
+ nextArrayFrom: configStream
+ 	"Each config array starts with #name. The appearance of another token of
+ 	that value indicates the beginning of a new configuration map for a prior
+ 	version of the configuration."
+ 	| oc |
+ 	oc := OrderedCollection new.
+ 	oc add: configStream next.
+ 	[configStream atEnd not and: [#name ~= configStream peek]]
+ 		whileTrue: [oc add: configStream next].
+ 	^ oc
+ !

Item was added:
+ ----- Method: MCConfiguration class>>nextFrom: (in category 'private') -----
+ nextFrom: configStream
+ 
+ 	| configArray configuration |
+ 	configArray := self nextArrayFrom: configStream.
+ 	configuration := (self concreteClassFor: configArray) new.
+ 	configArray pairsDo: [:key :value |
+ 		configuration initializeFromKey: key value: value].
+ 	^ configuration.
+ !

Item was added:
+ ----- Method: MCConfiguration class>>oldVersionOfFromArray: (in category 'private') -----
+ oldVersionOfFromArray: anArray
+ 	"For verifying backward compatability. This is the implementation
+ 	of #fromArray: prior to introduction of MCConfigurationExtended."
+ 	| configuration |
+ 	configuration := self new.
+ 	anArray pairsDo: [:key :value |
+ 		key = #repository
+ 			ifTrue: [configuration repositories add: (self repositoryFromArray: value)].
+ 		key = #dependency
+ 			ifTrue: [configuration dependencies add: (self dependencyFromArray: value)].
+ 		key = #name
+ 			ifTrue: [configuration name: value].
+ 	].
+ 	^configuration!

Item was added:
+ ----- Method: MCConfiguration class>>versionsFromStream: (in category 'private') -----
+ versionsFromStream: arrayStream
+ 	"Answer all versions with history list populated in each version."
+ 	| configuration history |
+ 	arrayStream atEnd ifTrue: [ ^ #() ].
+ 	configuration := self nextFrom: arrayStream.
+ 	history := self versionsFromStream: arrayStream.
+ 	history do: [ :ver | configuration addPriorVersion: ver ].
+ 	^ { configuration }, history.
+ !

Item was added:
+ ----- Method: MCConfiguration>>= (in category 'comparing') -----
+ = configuration
+ 	^ ((configuration class = self class
+ 		and: [configuration name = name])
+ 			and: [configuration dependencies = dependencies])
+ 				and: [configuration repositories = repositories]!

Item was added:
+ ----- Method: MCConfiguration>>addPriorVersion: (in category 'initialize') -----
+ addPriorVersion: mcConfig
+ 	"Do nothing, the original MCConfiguration format does not maintain history"!

Item was changed:
  ----- Method: MCConfiguration>>browse (in category 'actions') -----
  browse
  	| browser |
+ 	browser := MCConfigurationBrowser new configuration: self copyForEdit.
- 	browser := MCConfigurationBrowser new configuration: self.
  	name ifNotNil: [:nm | browser label: browser defaultLabel , ' ' , nm].
  	browser show!

Item was added:
+ ----- Method: MCConfiguration>>contentsOn: (in category 'printing') -----
+ contentsOn: aStream
+ 	self contentsOn: aStream keyPrefix: ''.
+ !

Item was added:
+ ----- Method: MCConfiguration>>contentsOn:keyPrefix: (in category 'printing') -----
+ contentsOn: aStream keyPrefix: prefix
+ 	"Prepend prefix to key values. If the prefix is a non-empty string, the resulting
+ 	key values will be ignored when parsing an original format MCConfiguration
+ 	from an extended format MCM file. This provides backward compatibility for
+ 	older images that need to read newer format MCM files."
+ 
+ 	name ifNotNil: [:n |
+ 		aStream cr.
+ 		aStream nextPutAll: prefix,'name '. 
+ 		aStream print: n].
+ 
+ 	repositories do: [:ea | 
+ 		aStream cr.
+ 		aStream nextPutAll: prefix,'repository '.
+ 		(MCConfiguration repositoryToArray: ea) printElementsOn: aStream].
+ 
+ 	dependencies do: [:ea | 
+ 		aStream cr.
+ 		aStream nextPutAll: prefix,'dependency '.
+ 		(MCConfiguration dependencyToArray: ea) printElementsOn: aStream].
+ !

Item was added:
+ ----- Method: MCConfiguration>>copyForEdit (in category 'copying') -----
+ copyForEdit
+ 	"Preparing to edit a configuration. Answer a new copy with the original
+ 	instance saved in version history, and with no author initials or timestamp.
+ 	The initials and timestamp are to be set immediately prior to saving an edited
+ 	version."
+ 	| config |
+ 	config := MCConfigurationExtended new.
+ 	config name: name copy.
+ 	config dependencies: dependencies copy.
+ 	config repositories: repositories copy.
+ 	config priorVersions addFirst: self.
+ 	^ config!

Item was added:
+ ----- Method: MCConfiguration>>copyWithoutHistory (in category 'copying') -----
+ copyWithoutHistory
+ 	^ self copy
+ !

Item was changed:
  ----- Method: MCConfiguration>>fileOutOn: (in category 'printing') -----
  fileOutOn: aStream
+ 	self fileOutOn: aStream keyPrefix: ''
+ !
- 	self writerClass fileOut: self on: aStream!

Item was added:
+ ----- Method: MCConfiguration>>fileOutOn:keyPrefix: (in category 'printing') -----
+ fileOutOn: aStream keyPrefix: prefix
+ 
+ 	aStream nextPut: $(.
+ 	self contentsOn: aStream keyPrefix: prefix.
+ 	aStream cr.
+ 	aStream nextPut: $).
+ !

Item was added:
+ ----- Method: MCConfiguration>>hash (in category 'comparing') -----
+ hash
+ 	^ (name hash bitXor: (dependencies hash)) bitXor: repositories hash
+ !

Item was added:
+ ----- Method: MCConfiguration>>initializeFromKey:value: (in category 'initialize') -----
+ initializeFromKey: key value: value
+ 	key = #repository
+ 		ifTrue: [self repositories add: (MCConfiguration repositoryFromArray: value)].
+ 	key = #dependency
+ 		ifTrue: [self dependencies add: (MCConfiguration dependencyFromArray: value)].
+ 	key = #name
+ 		ifTrue: [self name: value].
+ !

Item was changed:
  MCTool subclass: #MCConfigurationBrowser
+ 	instanceVariableNames: 'configuration dependencyIndex repositoryIndex activeEditWindow'
- 	instanceVariableNames: 'configuration dependencyIndex repositoryIndex'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'MonticelloConfigurations'!
  
  !MCConfigurationBrowser commentStamp: 'dtl 5/10/2010 21:48' prior: 0!
  A MCConfigurationBrowser displays an MCConfiguration, and edits the configuration to add or remove package dependencies and repository specifications. It allows a configuration to be stored in a repository or posted to an update stream.!

Item was added:
+ ----- Method: MCConfigurationBrowser>>activeEditWindow (in category 'morphic ui') -----
+ activeEditWindow
+ 	^activeEditWindow
+ !

Item was added:
+ ----- Method: MCConfigurationBrowser>>activeEditWindow: (in category 'morphic ui') -----
+ activeEditWindow: editWindow
+ 	"Set temporarily during the process of editing a version comment."
+ 	activeEditWindow ifNotNil: [:window | window delete].
+ 	activeEditWindow := editWindow.
+ !

Item was changed:
  ----- Method: MCConfigurationBrowser>>buttonSpecs (in category 'morphic ui') -----
  buttonSpecs
  	^ #(('Add' addDependency 'Add a dependency')
  		('Update' updateMenu 'Update dependencies')
  		('Install' installMenu 'Load/Merge/Upgrade into image')
  		('Up' up 'Move item up in list' canMoveUp)
  		('Down' down 'Move item down in list' canMoveDown)
  		('Remove' remove 'Remove item' canRemove)
  		('Save' store 'Store the configuration to a repository')
+ 		('Versions' versions 'Show prior versions of this configuration')
  		)!

Item was added:
+ ----- 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 storeVersion: configuration.
+ 			self inform: 'Saved ', configuration name]!

Item was changed:
  ----- Method: MCConfigurationBrowser>>defaultExtent (in category 'morphic ui') -----
  defaultExtent
+ 	^ 450 at 500!
- 	^ 360 at 500!

Item was added:
+ ----- 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 := UIManager default
+ 		edit: configuration comment
+ 		label: 'Enter or edit a comment for ', configuration name
+ 		accept: [:aText | | editingComplete |
+ 			editingComplete := UIManager default
+ 				confirm: 'Comment accepted' translated
+ 				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.
+ !

Item was changed:
  ----- Method: MCConfigurationBrowser>>store (in category 'actions') -----
  store
+ 	self activeEditWindow: nil. "Close previous if still open"
  	(self checkRepositories and: [self checkDependencies]) ifFalse: [^self].
+ 	self pickName ifNotNil: [:name | | originalName |
+ 		originalName := configuration name.
+ 		configuration name: name.
+ 		self enterVersionCommentAndCompleteWith: self nameForRestore: originalName ].!
- 	self pickName ifNotNil: [:name |
- 		self configuration name: name.
- 		self pickRepository ifNotNil: [:repo |
- 			repo storeVersion: self configuration]].!

Item was added:
+ ----- Method: MCConfigurationBrowser>>versions (in category 'actions') -----
+ versions
+ 	configuration priorVersions explore!

Item was added:
+ MCConfiguration subclass: #MCConfigurationExtended
+ 	instanceVariableNames: 'mcmVersion id authorInitials timeStamp comment priorVersions'
+ 	classVariableNames: 'HistoryLimit'
+ 	poolDictionaries: ''
+ 	category: 'MonticelloConfigurations'!
+ 
+ !MCConfigurationExtended commentStamp: 'dtl 4/13/2020 13:57' prior: 0!
+ A MCConfigurationExtended is a configuration with author initials, timestamp, comment, and a list of prior versions. Its external storage format is organized for compatibility with MCConfiguration, such that an image wtih support for only MCConfiguration can use configurations saved from a MCConfigurationExtended. The intended use is to enable documentation of configuration maps, and to allow modifications to a configuration map without loss of version history.!

Item was added:
+ ----- Method: MCConfigurationExtended class>>initialize (in category 'class initialization') -----
+ initialize
+ 
+ 	"Limit the number of prior versions in the history list to prevent MCM files from
+ 	becoming unnecessarily large over time. Versions are idenitified by a UUID
+ 	identifier, which should be sufficient for building a full version history if needed."
+ 	HistoryLimit := 10.!

Item was added:
+ ----- Method: MCConfigurationExtended>>= (in category 'comparing') -----
+ = configuration
+ 	^ (((super = configuration
+ 		and: [configuration authorInitials = authorInitials])
+ 			and: [configuration timeStamp = timeStamp])
+ 				and: [configuration id = id])
+ 					and: [configuration comment = comment].
+ !

Item was added:
+ ----- Method: MCConfigurationExtended>>addPriorVersion: (in category 'initialize') -----
+ addPriorVersion: mcConfig
+ 	priorVersions add: mcConfig!

Item was added:
+ ----- Method: MCConfigurationExtended>>authorInitials (in category 'accessing') -----
+ authorInitials
+ 	^ authorInitials
+ !

Item was added:
+ ----- Method: MCConfigurationExtended>>authorInitials: (in category 'accessing') -----
+ authorInitials: initials
+ 	authorInitials := initials
+ !

Item was added:
+ ----- Method: MCConfigurationExtended>>comment (in category 'accessing') -----
+ comment
+ 	^ comment
+ !

Item was added:
+ ----- Method: MCConfigurationExtended>>comment: (in category 'accessing') -----
+ comment: aString
+ 	comment := aString
+ !

Item was added:
+ ----- Method: MCConfigurationExtended>>contentsOn:keyPrefix: (in category 'printing') -----
+ contentsOn: aStream keyPrefix: prefix
+ 
+ 	super contentsOn: aStream keyPrefix: prefix.
+ 
+ 	mcmVersion ifNotNil: [:ver |
+ 		aStream cr.
+ 		aStream nextPutAll: prefix,'mcmVersion '. 
+ 		aStream print: ver].
+ 
+ 	id ifNotNil: [:uuid |
+ 		aStream cr.
+ 		aStream nextPutAll: prefix,'id '.
+ 		aStream print: uuid].
+ 
+ 	authorInitials ifNotNil: [:initials |
+ 		aStream cr.
+ 		aStream nextPutAll: prefix,'authorInitials '. 
+ 		aStream print: initials].
+ 
+ 	timeStamp ifNotNil: [:ts |
+ 		aStream cr.
+ 		aStream nextPutAll: prefix,'timeStamp '. 
+ 		aStream print: ts].
+ 
+ 	comment ifNotNil: [:c |
+ 		aStream cr.
+ 		aStream nextPutAll: prefix,'comment '. 
+ 		aStream print: c].
+ 
+ 	"Keys in the prior versions have a prefix to prevent them being parsed
+ 	into a MCConfiguration when an image that does not contain support for the
+ 	newer MCConfigurationExtended format. This allows older images to read
+ 	an MCM file with extended format and version history, treating it as if it
+ 	were data for the original MCConfiguration. See #copyWithoutKeyPrefix:
+ 	for removal of the prefix during parsing."
+ 	priorVersions do: [:e | e copyWithoutHistory contentsOn: aStream keyPrefix: 'X'].
+ !

Item was added:
+ ----- Method: MCConfigurationExtended>>copyForEdit (in category 'copying') -----
+ copyForEdit
+ 	"Preparing to edit a configuration. Answer a new copy with the original
+ 	instance saved in version history, and with no author initials or timestamp.
+ 	The initials and timestamp are to be set immediately prior to saving an edited
+ 	version."
+ 	| config |
+ 	config := super copyForEdit.
+ 	config priorVersions: priorVersions copy.
+ 	config priorVersions addFirst: self.
+ 	config authorInitials: nil.
+ 	config timeStamp: nil.
+ 	config comment: self comment copy.
+ 	config trimVersionList.
+ 	^ config!

Item was added:
+ ----- Method: MCConfigurationExtended>>copyWithoutHistory (in category 'copying') -----
+ copyWithoutHistory
+ 	"When a configuration is part of a version history, do not repeatedly
+ 	export its history."
+ 
+ 	| config |
+ 	config := self copy.
+ 	config priorVersions: OrderedCollection new.
+ 	^ config!

Item was added:
+ ----- Method: MCConfigurationExtended>>hash (in category 'comparing') -----
+ hash
+ 	^ (super hash bitOr: timeStamp hash) bitXor: id.
+ !

Item was added:
+ ----- Method: MCConfigurationExtended>>id (in category 'accessing') -----
+ id
+ 	^ id!

Item was added:
+ ----- Method: MCConfigurationExtended>>id: (in category 'accessing') -----
+ id: uuid
+ 	id := uuid!

Item was added:
+ ----- Method: MCConfigurationExtended>>initialize (in category 'initialize') -----
+ initialize
+ 	super initialize.
+ 	mcmVersion := '2'.
+ 	priorVersions := OrderedCollection new.!

Item was added:
+ ----- Method: MCConfigurationExtended>>initializeFromKey:value: (in category 'initialize') -----
+ initializeFromKey: key value: value
+ 	super initializeFromKey: key value: value.
+ 	key = #mcmVersion
+ 		ifTrue: [mcmVersion := value].
+ 	key = #id
+ 		ifTrue: [id := value].
+ 	key = #authorInitials
+ 		ifTrue: [authorInitials := value].
+ 	key = #timeStamp
+ 		ifTrue: [timeStamp := value].
+ 	key = #comment
+ 		ifTrue: [comment := value].
+ 
+ !

Item was added:
+ ----- Method: MCConfigurationExtended>>mcmVersion (in category 'accessing') -----
+ mcmVersion
+ 	^ mcmVersion
+ !

Item was added:
+ ----- Method: MCConfigurationExtended>>printOn: (in category 'printing') -----
+ printOn: aStream
+ 	super printOn: aStream.
+ 	aStream nextPutAll: ' ', name asString, ' ', timeStamp asString, ' (', id asString, ')'.!

Item was added:
+ ----- Method: MCConfigurationExtended>>priorVersions (in category 'accessing') -----
+ priorVersions
+ 	^ priorVersions
+ !

Item was added:
+ ----- Method: MCConfigurationExtended>>priorVersions: (in category 'accessing') -----
+ priorVersions: collection
+ 	priorVersions := collection
+ !

Item was added:
+ ----- Method: MCConfigurationExtended>>timeStamp (in category 'accessing') -----
+ timeStamp
+ 	^ timeStamp
+ !

Item was added:
+ ----- Method: MCConfigurationExtended>>timeStamp: (in category 'accessing') -----
+ timeStamp: aString
+ 	timeStamp := aString
+ !

Item was added:
+ ----- Method: MCConfigurationExtended>>trimVersionList (in category 'initialize') -----
+ trimVersionList
+ 	[priorVersions size > HistoryLimit]
+ 		whileTrue: [priorVersions removeLast].
+ !

Item was added:
+ ----- Method: MCConfigurationExtended>>versions (in category 'initialize') -----
+ versions
+ 	"myself with all prior versions"
+ 	^ { self } , priorVersions.
+ !

Item was changed:
  ----- Method: MCMcmWriter>>writeConfiguration: (in category 'writing') -----
  writeConfiguration: aConfiguration
+ 	aConfiguration fileOutOn: stream.
- 
- 	stream nextPut: $(.
- 	
- 	aConfiguration name ifNotNil: [:n |
- 		stream cr.
- 		stream nextPutAll: 'name '. 
- 		stream print: n].
- 
- 	aConfiguration repositories do: [:ea | 
- 		stream cr.
- 		stream nextPutAll: 'repository '.
- 		(MCConfiguration repositoryToArray: ea) printElementsOn: stream].
- 
- 	aConfiguration dependencies do: [:ea | 
- 		stream cr.
- 		stream nextPutAll: 'dependency '.
- 		(MCConfiguration dependencyToArray: ea) printElementsOn: stream].
- 
- 	stream cr.
- 	stream nextPut: $).
  !



More information about the Squeak-dev mailing list