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

commits at source.squeak.org commits at source.squeak.org
Wed Apr 15 23:56:50 UTC 2020


A new version of MonticelloConfigurations was added to project The Inbox:
http://source.squeak.org/inbox/MonticelloConfigurations-dtl.160.mcz

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

Name: MonticelloConfigurations-dtl.160
Author: dtl
Time: 13 April 2020, 2:00:59.804832 pm
UUID: 8db0c82b-3da4-4769-9922-b3a296e1e1bf
Ancestors: MonticelloConfigurations-mt.159

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.

=============== Diff against MonticelloConfigurations-mt.159 ===============

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."
+ 	| strm |
+ 	strm := #() writeStream.
+ 	configArray do: [ :token |
+ 		token caseOf: {
+ 				[#Xname ] -> [ strm nextPut: #name] .
+ 				[#Xrepository ] -> [ strm nextPut: #repository] .
+ 				[#Xdependency ] -> [ strm nextPut: #dependency] .
+ 				[#XmcmVersion] -> [ strm nextPut: #mcmVersion] .
+ 				[#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 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
+ 
+ 	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>>copyWithoutHistory (in category 'private') -----
+ 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 added:
+ MCConfiguration subclass: #MCConfigurationExtended
+ 	instanceVariableNames: 'mcmVersion authorInitials timeStamp comment priorVersions'
+ 	classVariableNames: ''
+ 	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>>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>>comment (in category 'accessing') -----
+ comment
+ 	^ comment
+ !

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].
+ 
+ 	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."
+ 	priorVersions do: [:e | e copyWithoutHistory contentsOn: aStream keyPrefix: 'X'].
+ !

Item was added:
+ ----- Method: MCConfigurationExtended>>copyWithoutHistory (in category 'private') -----
+ copyWithoutHistory
+ 	| config |
+ 	config := self copy.
+ 	config priorVersions removeAll.
+ 	^ config!

Item was added:
+ ----- Method: MCConfigurationExtended>>initialize (in category 'initialize') -----
+ initialize
+ 	super initialize.
+ 	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 = #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>>mcmVersion: (in category 'accessing') -----
+ mcmVersion: aString
+ 	mcmVersion := aString
+ !

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

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

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