[squeak-dev] The Inbox: Monticello-topa.490.mcz

commits at source.squeak.org commits at source.squeak.org
Fri Dec 2 15:44:49 UTC 2011


A new version of Monticello was added to project The Inbox:
http://source.squeak.org/inbox/Monticello-topa.490.mcz

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

Name: Monticello-topa.490
Author: topa
Time: 2 December 2011, 10:49:46.616 am
UUID: 460bc9a0-d113-4619-b46f-539ec5a25521
Ancestors: Monticello-cmm.489

Support for pluggable 
loaders and serializers for MCZ/MCD files.
This can be handy when extending The Monticello fromat 
without breaking too much.

=============== Diff against Monticello-cmm.489 ===============

Item was added:
+ ----- Method: MCMcdReader class>>initialize (in category 'as yet unclassified') -----
+ initialize
+ 	"MCMcdReader initialize"
+ 	"use super to populate loaders"
+ 	super initialize!

Item was added:
+ ----- Method: MCMcdReader class>>loaderDiff (in category 'as yet unclassified') -----
+ loaderDiff
+ 
+ 	^ 9999 -> [:reader | reader loadDiff]!

Item was added:
+ ----- Method: MCMcdReader class>>loaderDiffBinary (in category 'as yet unclassified') -----
+ loaderDiffBinary
+ 
+ 	^ 100 -> [:reader | reader loaderDiffBinary]!

Item was added:
+ ----- Method: MCMcdReader>>loadDiff (in category 'as yet unclassified') -----
+ loadDiff
+ 	| old new |
+ 	
+ 	definitions := OrderedCollection new.
+ 	(self zip membersMatching: 'old/*')
+ 		do: [:m | self extractDefinitionsFrom: m].
+ 	old := definitions asArray.
+ 	definitions := OrderedCollection new.
+ 	(self zip membersMatching: 'new/*')
+ 		do: [:m | self extractDefinitionsFrom: m].
+ 	new := definitions asArray.
+ 	
+ 	^ patch := self buildPatchFrom: old to: new.!

Item was added:
+ ----- Method: MCMcdReader>>loadDiffBinary (in category 'as yet unclassified') -----
+ loadDiffBinary
+ 
+ 	(self zip memberNamed: 'patch.bin') ifNotNil:
+ 		[:m | [^ patch := (DataStream on: m contentStream) next ]
+ 			on: Error do: [:fallThrough | ^ nil ]].!

Item was changed:
  ----- Method: MCMcdReader>>loadPatch (in category 'as yet unclassified') -----
  loadPatch
+ 	
+ 	^ self loadByLoaderBlock!
- 	| old new |
- 	(self zip memberNamed: 'patch.bin') ifNotNil:
- 		[:m | [^ patch := (DataStream on: m contentStream) next ]
- 			on: Error do: [:fallThrough ]].
- 	definitions := OrderedCollection new.
- 	(self zip membersMatching: 'old/*')
- 		do: [:m | self extractDefinitionsFrom: m].
- 	old := definitions asArray.
- 	definitions := OrderedCollection new.
- 	(self zip membersMatching: 'new/*')
- 		do: [:m | self extractDefinitionsFrom: m].
- 	new := definitions asArray.
- 	^ patch := self buildPatchFrom: old to: new.
- 	!

Item was added:
+ ----- Method: MCMcdWriter class>>initialize (in category 'as yet unclassified') -----
+ initialize
+ 	"MCMcdWriter initialize"
+ 	"use super to populate serializers"
+ 	super initialize!

Item was added:
+ ----- Method: MCMcdWriter class>>serializerBinary (in category 'as yet unclassified') -----
+ serializerBinary
+ 
+ 	^ [:writer :patch | writer writePatchAsBinary: patch]!

Item was added:
+ ----- Method: MCMcdWriter class>>serializerDefinition (in category 'as yet unclassified') -----
+ serializerDefinition
+ 
+ 	^ [:writer :patch | writer writePatchAsDefinition: patch]!

Item was changed:
  ----- Method: MCMcdWriter>>writePatch: (in category 'as yet unclassified') -----
  writePatch: aPatch
+ 	self writeWithAllSerializers: aPatch!
- 	| old new |
- 	old := OrderedCollection new.
- 	new := OrderedCollection new.
- 	aPatch operations do:
- 		[:ea |
- 		ea isRemoval ifTrue: [old add: ea definition].
- 		ea isAddition ifTrue: [new add: ea definition].
- 		ea isModification ifTrue: [old add: ea baseDefinition. new add: ea definition]].
- 	self writeOldDefinitions: old.
- 	self writeNewDefinitions: new.
- 	self addString: (self serializeInBinary: aPatch) at: 'patch.bin'.!

Item was added:
+ ----- Method: MCMcdWriter>>writePatchAsBinary: (in category 'as yet unclassified') -----
+ writePatchAsBinary: aPatch
+ 	self addString: (self serializeInBinary: aPatch) at: 'patch.bin'.!

Item was added:
+ ----- Method: MCMcdWriter>>writePatchAsDefinition: (in category 'as yet unclassified') -----
+ writePatchAsDefinition: aPatch
+ 
+ 	| old new |
+ 	old := OrderedCollection new.
+ 	new := OrderedCollection new.
+ 	aPatch operations do:
+ 		[:ea |
+ 		ea isRemoval ifTrue: [old add: ea definition].
+ 		ea isAddition ifTrue: [new add: ea definition].
+ 		ea isModification ifTrue: [old add: ea baseDefinition. new add: ea definition]].
+ 	self writeOldDefinitions: old.
+ 	self writeNewDefinitions: new!

Item was changed:
  MCVersionReader subclass: #MCMczReader
  	instanceVariableNames: 'zip infoCache'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Monticello-Storing'!
+ MCMczReader class
+ 	instanceVariableNames: 'loaders'!
+ MCMczReader class
+ 	instanceVariableNames: 'loaders'!

Item was added:
+ ----- Method: MCMczReader class>>allLoaderSelectors (in category 'as yet unclassified') -----
+ allLoaderSelectors
+ 
+ 	^ self class selectors select: [ :each | 
+ 		each ~= 'loaders'
+ 	and: [(each beginsWith: 'loader')
+ 	and: [each numArgs = 0]]]!

Item was added:
+ ----- Method: MCMczReader class>>initialize (in category 'as yet unclassified') -----
+ initialize
+ 	"MCMczReader initialize"
+ 
+ 	self populateLoaders.!

Item was added:
+ ----- Method: MCMczReader class>>loaderBinary (in category 'as yet unclassified') -----
+ loaderBinary
+ 
+ 	^ 100 -> [:reader | reader loadBinary].
+ 	!

Item was added:
+ ----- Method: MCMczReader class>>loaderSnapshot (in category 'as yet unclassified') -----
+ loaderSnapshot
+ 
+ 	^ 9999 -> [:reader | reader loadSnapshot]!

Item was added:
+ ----- Method: MCMczReader class>>loaders (in category 'as yet unclassified') -----
+ loaders
+ 
+ 	^ loaders!

Item was added:
+ ----- Method: MCMczReader class>>populateLoaders (in category 'as yet unclassified') -----
+ populateLoaders
+ 	" loaders will hold a Collection of associations of
+ 		priority -> [:OneArg | LoaderBlock]
+ 	and the arg will be the reader."
+ 	
+ 	loaders := self allLoaderSelectors
+ 		inject: (SortedCollection sortBlock: [:loader1 :loader2 | loader1 key <= loader2 key])
+ 		into: [:collection :selector |
+ 			collection add: (self perform: selector); yourself].!

Item was added:
+ ----- Method: MCMczReader>>definitions: (in category 'as yet unclassified') -----
+ definitions: anObject
+ 
+ 	definitions := anObject.!

Item was added:
+ ----- Method: MCMczReader>>loadBinary (in category 'as yet unclassified') -----
+ loadBinary
+ 
+ 	(self zip memberNamed: 'snapshot.bin') ifNotNil: [:m |
+ 		[^ definitions := (DataStream on: m contentStream) next definitions]
+ 		on: Error do: [:fallThrough | ^ nil]]!

Item was added:
+ ----- Method: MCMczReader>>loadByLoaderBlock (in category 'as yet unclassified') -----
+ loadByLoaderBlock
+ 
+ 	| loaderSorted defs|
+ 	loaderSorted := self class loaders collect: [:loader | loader value].
+ 	loaderSorted detect: [:loaderBlock | (defs := loaderBlock value: self) notNil].
+ 	^ defs
+ !

Item was changed:
  ----- Method: MCMczReader>>loadDefinitions (in category 'as yet unclassified') -----
  loadDefinitions
+ 
+ 	^ self loadByLoaderBlock
- 	definitions := OrderedCollection new.
- 	(self zip memberNamed: 'snapshot.bin') ifNotNil:
- 		[:m | [^ definitions := (DataStream on: m contentStream) next definitions]
- 			on: Error do: [:fallThrough ]].
- 	"otherwise"
- 	(self zip membersMatching: 'snapshot/*')
- 		do: [:m | self extractDefinitionsFrom: m].
  !

Item was added:
+ ----- Method: MCMczReader>>loadSnapshot (in category 'as yet unclassified') -----
+ loadSnapshot
+ 
+ 	definitions :=OrderedCollection new.
+ 	(self zip membersMatching: 'snapshot/*')
+ 		do: [:m | self extractDefinitionsFrom: m].
+ 	^ definitions
+ 		!

Item was changed:
  MCWriter subclass: #MCMczWriter
  	instanceVariableNames: 'zip infoWriter'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Monticello-Storing'!
+ MCMczWriter class
+ 	instanceVariableNames: 'serializers'!
+ MCMczWriter class
+ 	instanceVariableNames: 'serializers'!

Item was added:
+ ----- Method: MCMczWriter class>>allSerializerSelectors (in category 'as yet unclassified') -----
+ allSerializerSelectors
+ 
+ 	^ self class selectors select: [ :each | 
+ 		each ~= 'serializers'
+ 	and: [(each beginsWith: 'serializer')
+ 	and: [each numArgs = 0]]]!

Item was added:
+ ----- Method: MCMczWriter class>>initialize (in category 'as yet unclassified') -----
+ initialize
+ 	"MCMczWriter initialize"
+ 
+ 	self populateSerializers.!

Item was added:
+ ----- Method: MCMczWriter class>>populateSerializers (in category 'as yet unclassified') -----
+ populateSerializers
+ 	" serializers  will hold a Collection of
+ 		[:OneArg :TwoArg | WriterBlock]
+ 	and 
+ 		the first argument will be the writer
+ 	and
+ 		the second argument will be the snapshot."
+ 	
+ 	serializers := self allSerializerSelectors collect: [:selector | self perform: selector].!

Item was added:
+ ----- Method: MCMczWriter class>>serializerBinary (in category 'as yet unclassified') -----
+ serializerBinary
+ 
+ 	^ [:writer :snapshot | writer writeSnapshotAsBinary: snapshot]!

Item was added:
+ ----- Method: MCMczWriter class>>serializerDefinition (in category 'as yet unclassified') -----
+ serializerDefinition
+ 
+ 	^ [:writer :snapshot | writer writeSnapshotAsDefinition: snapshot]!

Item was added:
+ ----- Method: MCMczWriter class>>serializers (in category 'as yet unclassified') -----
+ serializers
+ 
+ 	^ serializers!

Item was added:
+ ----- Method: MCMczWriter>>serializeInFuel: (in category 'serializing') -----
+ serializeInFuel: aSnapshot
+ 
+ 	(self class environment classNamed: #FLSerializer) ifNotNil: [:serializerClass |
+ 		^ serializerClass serializeToByteArray: aSnapshot]!

Item was changed:
  ----- Method: MCMczWriter>>writeSnapshot: (in category 'visiting') -----
  writeSnapshot: aSnapshot
+ 	self writeWithAllSerializers: aSnapshot.!
- 	self addString: (self serializeDefinitions: aSnapshot definitions) at: 'snapshot/source.', self snapshotWriterClass extension.
- 	self addString: (self serializeInBinary: aSnapshot) at: 'snapshot.bin'!

Item was added:
+ ----- Method: MCMczWriter>>writeSnapshotAsBinary: (in category 'visiting') -----
+ writeSnapshotAsBinary: aSnapshot
+ 	self addString: (self serializeInBinary: aSnapshot) at: 'snapshot.bin'!

Item was added:
+ ----- Method: MCMczWriter>>writeSnapshotAsDefinition: (in category 'visiting') -----
+ writeSnapshotAsDefinition: aSnapshot
+ 	self addString: (self serializeDefinitions: aSnapshot definitions) at: 'snapshot/source.', self snapshotWriterClass extension.!

Item was added:
+ ----- Method: MCMczWriter>>writeWithAllSerializers: (in category 'visiting') -----
+ writeWithAllSerializers: snapshot
+ 
+ 	self class serializers do: [:serializerBlock | 
+ 		serializerBlock value: self value: snapshot].
+ !




More information about the Squeak-dev mailing list