[Pkg] DeltaStreams: DeltaStreams-Model-gk.14.mcz

squeak-dev-noreply at lists.squeakfoundation.org squeak-dev-noreply at lists.squeakfoundation.org
Fri Sep 4 06:56:49 UTC 2009


A new version of DeltaStreams-Model was added to project DeltaStreams:
http://www.squeaksource.com/DeltaStreams/DeltaStreams-Model-gk.14.mcz

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

Name: DeltaStreams-Model-gk.14
Author: gk
Time: 4 September 2009, 8:56:20 am
UUID: d8611b99-d070-4753-8cf3-8fe090252412
Ancestors: DeltaStreams-Model-gk.13

Lots of changes, refactorings and greener tests. Tirade hooked in.

=============== Diff against DeltaStreams-Model-gk.13 ===============

Item was added:
+ ----- Method: DSMethodProtocolChange>>protocolChange: (in category 'accessing') -----
+ protocolChange: assoc
+ 	self oldProtocol: assoc key.
+ 	self protocol: assoc value!

Item was changed:
  ----- Method: DSClassChange>>initialize (in category 'initialize-release') -----
  initialize
+ 	super initialize.
  	self superclassName: #Object.
  	self instVarNames: Array new.
  	self classVarNames: Array new.
  	self poolDictionaryNames: Array new.
  	self category: Categorizer default.
  	self type: #normal.
  	self comment: ''.
  	self stamp: nil.
  	self classInstVarNames: Array new.!

Item was changed:
  ----- Method: DSBasicClassChange>>fromClass: (in category 'initialize-release') -----
  fromClass: aClass
+ 	"Always use the name."
  
+ 	self className: aClass name!
- 	self setClass: aClass!

Item was changed:
  ----- Method: DSAnnotatedObject>>timeStamp (in category 'accessing') -----
  timeStamp
+ 	"If you just want to show it, use #timeStampString."
+ 	
+ 	^TimeStamp fromString: self timeStampString!
- 	^timeStamp!

Item was changed:
  ----- Method: DSMethodSourceChange>>newMethod: (in category 'accessing') -----
  newMethod: aCompiledMethod
+ 	self method: aCompiledMethod!
- 	self newSource: (self sourceFromMethod: aCompiledMethod).
- 	self newStamp: aCompiledMethod timeStamp.!

Item was changed:
  ----- Method: DSMethodChange>>fromClass:selector: (in category 'initialize-release') -----
  fromClass: aClass selector: aSelector
+ 	"Initiate this method change from given class and selector
+ 	by extracting all attributes from it."
+ 
+ 	self className: aClass name;
+ 		selector: aSelector;
+ 		method: (aClass methodDictionary at: aSelector);
+ 		protocol: (aClass organization categoryOfElement: aSelector)
- 	super fromClass: aClass selector: aSelector.
- 	self method: (aClass methodDictionary at: aSelector).
- 	self protocol: (aClass organization categoryOfElement: aSelector)
  	!

Item was added:
+ DSMethodChange subclass: #DSMethodSelectorChange
+ 	instanceVariableNames: 'oldSelector'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'DeltaStreams-Model-Method'!

Item was added:
+ ----- Method: DSClassCategoryChange class>>className:category:oldCategory: (in category 'instance creation') -----
+ className: aClassName
+ category: aCategory
+ oldCategory: oldCategory
+ 						
+ 	^(self className: aClassName)
+ 		category: aCategory;
+ 		oldCategory: oldCategory;
+ 		yourself
+ !

Item was added:
+ ----- Method: DSClassCategoryChange class>>className:superclassName:instVarNames:classVarNames:poolDictionaryNames:category:type:classInstVarNames:comment:stamp:oldCategory: (in category 'instance creation') -----
+ className: aClassName
+ superclassName: superclassName
+ instVarNames: instVarNames
+ classVarNames: classVarNames
+ poolDictionaryNames: poolDictionaryNames
+ category: aCategory
+ type: typeOfClass
+ classInstVarNames: metaInstVarNames
+ comment: classComment
+ stamp: commentStamp
+ oldCategory: oldCategory
+ 						
+ 	^(self className: aClassName)
+ 		superclassName: superclassName;
+ 		instVarNames: instVarNames;
+ 		classVarNames: classVarNames;
+ 		poolDictionaryNames: poolDictionaryNames;
+ 		category: aCategory;
+ 		type: typeOfClass;
+ 		classInstVarNames: metaInstVarNames;
+ 		comment: classComment;
+ 		stamp: commentStamp;
+ 		oldCategory: oldCategory;
+ 		yourself
+ !

Item was added:
+ ----- Method: DSMethodChange>>fullClassName (in category 'accessing') -----
+ fullClassName
+ 	"Copied from MCMethodDefinition."
+ 
+ 	^ meta
+ 		ifFalse: [self className]
+ 		ifTrue: [
+ 			(self actualClass isNil or: [ self actualClass isTrait ])
+ 				ifFalse: [self className, ' class']
+ 				ifTrue: [self className, ' classSide']]!

Item was added:
+ ----- Method: DSMethodChange class>>tiradeClassName:selector:category:source:stamp: (in category 'as yet unclassified') -----
+ tiradeClassName: aClassName selector: selector category: aCategory source: source stamp: stamp
+ 	^(self className: aClassName)
+ 		tiradeSelector: selector;
+ 		tiradeCategory: aCategory;
+ 		tiradeSource: source;
+ 		tiradeStamp: stamp;
+ 		yourself!

Item was changed:
  Object subclass: #DSAnnotatedObject
+ 	instanceVariableNames: 'properties'
- 	instanceVariableNames: 'timeStamp properties'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'DeltaStreams-Model-Base'!
  
+ !DSAnnotatedObject commentStamp: 'gk 8/3/2009 16:37' prior: 0!
- !DSAnnotatedObject commentStamp: 'gk 3/18/2009 16:06' prior: 0!
  An abstract superclass for anything that can have named properties and a creation timeStamp.
+ The properties Dictionary is lazily initialized, the timeStamp is set on creation.!
- The properties Dictionary is lazily initialized.!

Item was added:
+ ----- Method: DSMethodChange>>actualClass (in category 'accessing') -----
+ actualClass
+ 	"Copied from MCMethodDefinition."
+ 
+ 	^Smalltalk at: className
+ 		ifPresent: [:class | meta ifTrue: [class classSide] ifFalse: [class]]!

Item was changed:
  ----- Method: DSCompositeClassDeletedChange>>fromClass: (in category 'initialize-release') -----
  fromClass: aClass
  	"We add changes corresponding to removing every bit individually.
+ 	This is in order to be able to do a full revert later."
- 	This is in order to be able to do a full revert later.
- 	
- 	NOTE: Do not use this method directly, use instead:
- 	
- 		DSClassRemovedChange fromClass: aClass
- 	"
  
  	aClass theNonMetaClass selectors do: [:sel | self
  		add: (DSMethodRemovedChange fromClass: aClass theNonMetaClass selector: sel)].
  	aClass theMetaClass selectors do: [:sel | self
  		add: (DSMethodRemovedChange fromClass: aClass theMetaClass selector: sel)].
  
  	self add: (DSClassRemovedChange new fromClass: aClass)!

Item was changed:
  ----- Method: DSChange class>>fromChange: (in category 'instance creation') -----
  fromChange: aChange
+ 
  	^ self new fromChange: aChange; yourself!

Item was added:
+ ----- Method: DSClassChange class>>className:superclassName:instVarNames:classVarNames:poolDictionaryNames:category:type:classInstVarNames:comment:stamp: (in category 'instance creation') -----
+ className: aClassName
+ superclassName: superclassName
+ instVarNames: instVarNames
+ classVarNames: classVarNames
+ poolDictionaryNames: poolDictionaryNames
+ category: aCategory
+ type: typeOfClass
+ classInstVarNames: metaInstVarNames
+ comment: classComment
+ stamp: commentStamp
+ 						
+ 	^(self className: aClassName)
+ 		superclassName: superclassName;
+ 		instVarNames: instVarNames;
+ 		classVarNames: classVarNames;
+ 		poolDictionaryNames: poolDictionaryNames;
+ 		category: aCategory;
+ 		type: typeOfClass;
+ 		classInstVarNames: metaInstVarNames;
+ 		comment: classComment;
+ 		stamp: commentStamp;
+ 		yourself!

Item was added:
+ ----- Method: DSMethodChange>>category: (in category 'accessing') -----
+ category: aCategory
+ 
+ 	self protocol: aCategory!

Item was added:
+ ----- Method: DSMethodChange>>selector: (in category 'accessing') -----
+ selector: aString
+ 	selector := aString asSymbol!

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

Item was changed:
  DSClassChange subclass: #DSClassCategoryChange
  	instanceVariableNames: 'oldCategory'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'DeltaStreams-Model-Class'!
+ 
+ !DSClassCategoryChange commentStamp: 'gk 8/5/2009 23:41' prior: 0!
+ A change of category of a class.!

Item was added:
+ ----- Method: DSMethodChange>>hash (in category 'comparing') -----
+ hash
+ "This is just for comparing of group keys. See the comment in #=."
+ 	^ (super hash bitXor: meta hash) bitXor: selector hash!

Item was added:
+ ----- Method: DSMethodChange>>isMethodChange (in category 'testing') -----
+ isMethodChange
+ 	^ true!

Item was added:
+ ----- Method: DSMethodSelectorChange>>asAntiChange (in category 'anti') -----
+ asAntiChange
+ 	^ super asAntiChange
+ 		oldSelector: selector;
+ 		newSelector: oldSelector;
+ 		yourself!

Item was changed:
  ----- Method: DSChange>>fromChange: (in category 'initialize-release') -----
  fromChange: aChange
  	aChange propertiesDo: [:key :val |
  		self propertyAt: key put: val].
+ 	self timeStampString: aChange timeStampString!
- 	timeStamp := aChange timeStamp.!

Item was added:
+ ----- Method: DSAnnotatedObject>>timeStampString: (in category 'private') -----
+ timeStampString: aString
+ 	self propertyAt: #timeStamp put: aString!

Item was changed:
  ----- Method: DSClassChange>>fromClass: (in category 'initialize-release') -----
  fromClass: aClass
  	"We extract all needed attributes from the class so that we can recreate it."
  
  	| class metaclass |
- 	super fromClass: aClass.
  	class := aClass theNonMetaClass.
+ 	self className: class name.
  	metaclass := aClass theMetaClass.
  
  	self superclassName: class superclass name.
  	self instVarNames: class instVarNames.
  	self classVarNames: class classVarNames asArray.
  	self poolDictionaryNames: class poolDictionaryNames.
  	self category: class category.
  	self type: class typeOfClass.
  	self classInstVarNames: metaclass instVarNames.
+ 	self comment: class organization classComment asString.
- 	self comment: class organization classComment.
  	self stamp: class organization commentStamp.!

Item was added:
+ ----- Method: DSMethodSelectorChange>>newSelector (in category 'accessing') -----
+ newSelector
+ 	^ selector!

Item was added:
+ ----- Method: DSMethodProtocolChange class>>className:selector:protocol:source:stamp:oldProtocol: (in category 'as yet unclassified') -----
+ className: aClassName selector: selector protocol: newProtocol source: source stamp: stamp oldProtocol: oldProtocol
+ 	^ (self className: aClassName)
+ 		selector: selector;
+ 		protocol: newProtocol;
+ 		source: source;
+ 		stamp: stamp;
+ 		oldProtocol: oldProtocol;
+ 		yourself!

Item was changed:
  DSAnnotatedObject subclass: #DSChange
+ 	instanceVariableNames: ''
- 	instanceVariableNames: 'number'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'DeltaStreams-Model-Base'!
  
+ !DSChange commentStamp: 'gk 9/2/2009 19:02' prior: 0!
+ An abstract super class for all changes that a DSDelta can hold. A DSChange object should only hold "simple data" and not refer to the classes themselves. This makes them easy to construct, manipulate and serialize without affecting (or need) the real classes.!
- !DSChange commentStamp: 'gk 4/21/2009 23:41' prior: 0!
- An abstract super class for all changes that a DSDelta holds. A DSChange object should only hold "simple data" and not refer to the classes themselves. This makes them easy to construct, manipulate and serialize without affecting (or need) the real classes.
- 
- A DSChange has a number to be able to maintain ordering - timestamping is not enough when things are going fast. A DSChange should ONLY exist in one given Delta at time, we verify this by checking that number is indeed nil when the change is added to the DSDelta.!

Item was added:
+ ----- Method: DSDelta>>removeChange: (in category 'changes') -----
+ removeChange: aChange
+ 
+ 	| change |
+ 	change := self changes remove: change.
+ 	self grouper ifNotNil: [self grouper remove: change].
+ 	self changed: #changeList.
+ 	^ change!

Item was changed:
  ----- Method: DSAnnotatedObject>>propertyAt:put: (in category 'properties') -----
  propertyAt: aSymbol put: value
  
+ 	properties ifNil: [properties := Dictionary new: 1]. "often we just store timestamp"
- 	properties ifNil: [properties := Dictionary new].
  	^ properties at: aSymbol put: value!

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

Item was changed:
  ----- Method: DSMethodChange>>fromChange: (in category 'initialize-release') -----
  fromChange: aChange
  	super fromChange: aChange.
+ 	self className: aChange className.
+ 	self selector: aChange selector.
+ 	self meta: aChange meta.
  	self source: aChange source.
  	self protocol: aChange protocol.
  	self stamp: aChange stamp.	!

Item was added:
+ ----- Method: DSAnnotatedObject>>timeStampString (in category 'accessing') -----
+ timeStampString
+ 	^self propertyAt: #timeStamp!

Item was added:
+ ----- Method: DSClassNameChange class>>className:superclassName:instVarNames:classVarNames:poolDictionaryNames:category:type:classInstVarNames:comment:stamp:oldName: (in category 'instance creation') -----
+ className: aClassName
+ superclassName: superclassName
+ instVarNames: instVarNames
+ classVarNames: classVarNames
+ poolDictionaryNames: poolDictionaryNames
+ category: aCategory
+ type: typeOfClass
+ classInstVarNames: metaInstVarNames
+ comment: classComment
+ stamp: commentStamp
+ oldName: oldClassName
+ 						
+ 	^(self className: aClassName)
+ 		superclassName: superclassName;
+ 		instVarNames: instVarNames;
+ 		classVarNames: classVarNames;
+ 		poolDictionaryNames: poolDictionaryNames;
+ 		category: aCategory;
+ 		type: typeOfClass;
+ 		classInstVarNames: metaInstVarNames;
+ 		comment: classComment;
+ 		stamp: commentStamp;
+ 		oldName: oldClassName;
+ 		yourself
+ !

Item was changed:
+ ----- Method: DSChange>>visitDecorators: (in category 'decorators') -----
- ----- Method: DSChange>>visitDecorators: (in category 'flags') -----
  visitDecorators: aVisitor
  	"here the visitor gives the decorators a chance to inject behavior"
  	self decorators do: [:ea | ea accept: self for: aVisitor]!

Item was added:
+ ----- Method: DSBasicClassChange class>>tiradeClassName: (in category 'instance creation') -----
+ tiradeClassName: aName
+ 	^ self new
+ 		tiradeClassName: aName;
+ 		yourself!

Item was added:
+ ----- Method: DSMethodSelectorChange>>oldName: (in category 'accessing') -----
+ oldName: aString
+ 	oldSelector := aString asSymbol!

Item was added:
+ ----- Method: DSDelta>>addClassChange:from: (in category 'applying') -----
+ addClassChange: changeClass from: event
+ 	"Extract all relevant information from the event
+ 	to create and add a class change of given class name."
+ 
+ 	| class metaclass |
+ 	class := event itemClass theNonMetaClass.
+ 	metaclass := event itemClass theMetaClass.
+ 	^self add: (
+ 		self className: class name
+ 			changeClass: changeClass
+ 			superclassName: class superclass name
+ 			instVarNames: class instVarNames
+ 			classVarNames: class classVarNames asArray
+ 			poolDictionaryNames: class poolDictionaryNames
+ 			category: class category
+ 			type: class typeOfClass
+ 			classInstVarNames: metaclass instVarNames
+ 			comment: class organization classComment asString
+ 			stamp: class organization commentStamp)!

Item was changed:
  ----- Method: DSClassChange>>poolDictionaryNames (in category 'accessing') -----
  poolDictionaryNames
  	^poolDictionaryNames!

Item was added:
+ ----- Method: DSDelta>>asAntiDelta (in category 'applying') -----
+ asAntiDelta
+ 	"Return a new Delta that, when applied, reverts each change of this Delta
+ 	in reverse order. Each change should have enough information to create
+ 	an anti change from itself."
+ 
+ 	| anti |
+ 	self isRevertable ifFalse: [DSDeltaNotRevertableException signal].
+ 	anti := DSDelta name: 'undo ' translated, self name.
+ 	self propertiesDo: [:key :val | anti propertyAt: key put: val]. 
+ 	self changes reverseDo: [:each | anti add: each asAntiChange]. 
+ 	^anti!

Item was added:
+ ----- Method: DSDelta>>addMethodChange:from: (in category 'applying') -----
+ addMethodChange: changeClass from: event
+ 	"Extract all relevant information from the event
+ 	to create and add a method change of given class name."
+ 
+ 	| method selector class category |
+ 	category := event itemProtocol.
+ 	method := event item "Method".
+ 	"Do not ask me why we need to do it like the next three lines..."
+ 	selector := event itemSelector.
+ 	selector ifNil: [selector := event itemMethod sourceSelector].
+ 	selector ifNil: [selector := event itemMethod selector].
+ 	class := event itemClass.
+ 	^self add: (
+ 		self className: class name
+ 			selector: selector
+ 			change: changeClass
+ 			category: category
+ 			source: method getSource asString
+ 			stamp: method timeStamp)!

Item was added:
+ ----- Method: DSMethodSelectorChange>>oldSelector: (in category 'accessing') -----
+ oldSelector: aString
+ 	oldSelector := aString asSymbol!

Item was changed:
  ----- Method: DSMethodChange>>protocol: (in category 'accessing') -----
  protocol: aProtocol
+ 
  	protocol := aProtocol
  		ifNil: [Categorizer default]
  		ifNotNil: [aProtocol asSymbol]!

Item was added:
+ ----- Method: DSMethodSelectorChange>>isMethodName (in category 'testing') -----
+ isMethodName
+ 	^true!

Item was added:
+ ----- Method: DSDelta>>className:selector:change:category:source:stamp: (in category 'building') -----
+ className: className
+ selector: selector
+ change: changeClassName
+ category: category
+ source: source
+ stamp: stamp
+ 	"Create and return a method change.
+ 	It is not added to this Delta."
+ 	
+ 	^(self getClass: changeClassName)
+ 		className: className
+ 		selector: selector
+ 		category: category
+ 		source: source
+ 		stamp: stamp!

Item was added:
+ ----- Method: DSMethodChange>>meta: (in category 'accessing') -----
+ meta: aBoolean
+ 
+ 	meta := aBoolean!

Item was changed:
  ----- Method: DSMethodChange>>method: (in category 'initialize-release') -----
  method: aCompiledMethod
+ 	self source: aCompiledMethod getSource asString.
- 	self source: (self sourceFromMethod: aCompiledMethod).
  	self stamp: aCompiledMethod timeStamp.!

Item was changed:
  ----- Method: DSAnnotatedObject>>initialize (in category 'initialize-release') -----
  initialize
  
+ 	self timeStamp: TimeStamp now!
- 	timeStamp := TimeStamp now!

Item was changed:
+ DSBasicClassChange subclass: #DSMethodChange
+ 	instanceVariableNames: 'selector meta source protocol stamp'
- DSBasicMethodChange subclass: #DSMethodChange
- 	instanceVariableNames: 'source protocol stamp'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'DeltaStreams-Model-Method'!
+ 
+ !DSMethodChange commentStamp: 'gk 8/3/2009 15:31' prior: 0!
+ An abstract super class for all actions affecting a specific method:
+ 
+ selector: (Symbol) the method selector
+ meta: (Boolean) true if defined on the metaclass, false if defined on the class!

Item was added:
+ ----- Method: DSMethodSourceChange class>>className:selector:method:oldMethod: (in category 'as yet unclassified') -----
+ className: aClassName selector: selector method: newMethod oldMethod: oldMethod
+ 	^ (self className: aClassName)
+ 		selector: selector;
+ 		oldMethod: oldMethod;
+ 		newMethod: newMethod;
+ 		yourself!

Item was added:
+ ----- Method: DSMethodChange>>isMeta (in category 'testing') -----
+ isMeta
+ 	^ meta!

Item was changed:
  ----- Method: DSDelta>>revert (in category 'applying') -----
  revert
  	"Revert this delta by applying its anti Delta to the image."
  
+ 	^self asAntiDelta apply!
- 	^self asAntiChange apply!

Item was changed:
  ----- Method: DSBasicClassChange class>>className: (in category 'instance creation') -----
+ className: aName
+ 	^ self new
+ 		className: aName;
- className: aClassName
- 	^self new
- 		className: aClassName;
  		yourself!

Item was changed:
  ----- Method: DSMethodProtocolChange>>newProtocol: (in category 'accessing') -----
  newProtocol: aProtocol
+ 
  	self protocol: aProtocol!

Item was added:
+ ----- Method: DSClassCommentChange class>>className:superclassName:instVarNames:classVarNames:poolDictionaryNames:category:type:classInstVarNames:comment:oldComment:stamp:oldStamp: (in category 'as yet unclassified') -----
+ className: aClassName
+ superclassName: superclassName
+ instVarNames: instVarNames
+ classVarNames: classVarNames
+ poolDictionaryNames: poolDictionaryNames
+ category: aCategory
+ type: typeOfClass
+ classInstVarNames: metaInstVarNames
+ comment: classComment
+ oldComment: oldComment
+ stamp: commentStamp
+ oldStamp: oldStamp
+ 						
+ 	^(self className: aClassName)
+ 		superclassName: superclassName;
+ 		instVarNames: instVarNames;
+ 		classVarNames: classVarNames;
+ 		poolDictionaryNames: poolDictionaryNames;
+ 		category: aCategory;
+ 		type: typeOfClass;
+ 		classInstVarNames: metaInstVarNames;
+ 		comment: classComment;
+ 		stamp: commentStamp;
+ 		oldComment: oldComment;
+ 		oldStamp: oldStamp;
+ 		yourself
+ !

Item was added:
+ ----- Method: DSMethodSelectorChange>>isName (in category 'testing') -----
+ isName
+ 	^true!

Item was changed:
  DSBasicClassChange subclass: #DSClassChange
  	instanceVariableNames: 'superclassName instVarNames classVarNames classInstVarNames poolDictionaryNames category type comment stamp'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'DeltaStreams-Model-Class'!
  
+ !DSClassChange commentStamp: 'gk 8/5/2009 23:50' prior: 0!
+ All class changes contain the full snapshot of all class attributes, then subclass have complementary "old" attributes.
+ This means we carry more information than needed, but that gives us a higher level of making sure changes may be safe.
+ For example, changing a class comment in a class that has a different super class than expected might be a good signal to not perform that change.!
- !DSClassChange commentStamp: '<historical>' prior: 0!
- This action must hold all information that is mandatory to supply in order to create (or remove) a class - which means quite a lot of fields. When we later change a class (the DSClassChanged* classes) we are much more fine granular.
- 
- Note that this change only creates the class - it does not add methods or a class comment. See DSCompositeClassAddedChange.!

Item was added:
+ ----- Method: DSMethodSelectorChange>>applyUsing: (in category 'applying') -----
+ applyUsing: anApplier
+ 	^ anApplier applyMethodName: self!

Item was added:
+ ----- Method: DSDelta>>getClass: (in category 'private') -----
+ getClass: classOrSymbol
+ 	"Lookup or return if not a symbol."
+ 
+ 	classOrSymbol isSymbol ifTrue: [
+ 		^Smalltalk at: classOrSymbol].
+ 	^classOrSymbol!

Item was added:
+ ----- Method: DSMethodChange>>= (in category 'comparing') -----
+ = aChange
+ "This is just for comparing of group keys. See the comment in DSClassChange>>=.
+ 
+ Group keys for method changes depend on the class/metaclass separation and the selector, in addition to what is required for class changes to group together"
+ 	^ super = aChange and: [meta == aChange meta] and: [selector == aChange selector]!

Item was added:
+ ----- Method: DSMethodChange class>>fromClass:selector: (in category 'as yet unclassified') -----
+ fromClass: aClass selector: selector
+ 	"Create this method change from given class and selector
+ 	by extracting all attributes from it."
+ 	
+ 	^ self new fromClass: aClass selector: selector; yourself!

Item was added:
+ ----- Method: DSClassTypeChange class>>className:superclassName:instVarNames:classVarNames:poolDictionaryNames:category:type:classInstVarNames:comment:stamp:oldType: (in category 'as yet unclassified') -----
+ className: aClassName
+ superclassName: superclassName
+ instVarNames: instVarNames
+ classVarNames: classVarNames
+ poolDictionaryNames: poolDictionaryNames
+ category: aCategory
+ type: typeOfClass
+ classInstVarNames: metaInstVarNames
+ comment: classComment
+ stamp: commentStamp
+ oldType: oldTypeOfClass
+ 						
+ 	^(self className: aClassName)
+ 		superclassName: superclassName;
+ 		instVarNames: instVarNames;
+ 		classVarNames: classVarNames;
+ 		poolDictionaryNames: poolDictionaryNames;
+ 		category: aCategory;
+ 		type: typeOfClass;
+ 		classInstVarNames: metaInstVarNames;
+ 		comment: classComment;
+ 		stamp: commentStamp;
+ 		oldType: oldTypeOfClass;
+ 		yourself
+ !

Item was added:
+ ----- Method: DSMethodChange class>>className:selector:category:source:stamp: (in category 'as yet unclassified') -----
+ className: aClassName selector: selector category: aCategory source: source stamp: stamp
+ 	^(self className: aClassName)
+ 		selector: selector;
+ 		category: aCategory;
+ 		source: source;
+ 		stamp: stamp;
+ 		yourself!

Item was added:
+ ----- Method: DSMethodSourceChange class>>className:selector:protocol:source:stamp:oldSource:oldStamp: (in category 'as yet unclassified') -----
+ className: aClassName
+ selector: selector
+ protocol: protocol
+ source: source
+ stamp: stamp
+ oldSource: oldSource
+ oldStamp: oldStamp
+ 
+ 	^ (self className: aClassName)
+ 		selector: selector;
+ 		protocol: protocol;
+ 		source: source;
+ 		stamp: stamp;
+ 		oldSource: oldSource;
+ 		oldStamp: oldStamp;
+ 		yourself!

Item was added:
+ ----- Method: DSMethodSelectorChange>>newName: (in category 'accessing') -----
+ newName: aString
+ 	self selector: aString!

Item was added:
+ ----- Method: DSVarsChange class>>className:superclassName:instVarNames:classVarNames:poolDictionaryNames:category:type:classInstVarNames:comment:stamp:oldVars: (in category 'as yet unclassified') -----
+ className: aClassName
+ superclassName: superclassName
+ instVarNames: instVarNames
+ classVarNames: classVarNames
+ poolDictionaryNames: poolDictionaryNames
+ category: aCategory
+ type: typeOfClass
+ classInstVarNames: metaInstVarNames
+ comment: classComment
+ stamp: commentStamp
+ oldVars: oldVarNames
+ 						
+ 	^(self className: aClassName)
+ 		superclassName: superclassName;
+ 		instVarNames: instVarNames;
+ 		classVarNames: classVarNames;
+ 		poolDictionaryNames: poolDictionaryNames;
+ 		category: aCategory;
+ 		type: typeOfClass;
+ 		classInstVarNames: metaInstVarNames;
+ 		comment: classComment;
+ 		stamp: commentStamp;
+ 		oldVars: oldVarNames;
+ 		yourself!

Item was changed:
+ ----- Method: DSChange>>decorator:enable: (in category 'decorators') -----
- ----- Method: DSChange>>decorator:enable: (in category 'flags') -----
  decorator: aClass enable: enable
  	^ enable
  		ifTrue: [self addDecorator: aClass]
  		ifFalse: [self removeDecorator: aClass]!

Item was added:
+ ----- Method: DSClassCommentChange>>oldComment:stamp: (in category 'accessing') -----
+ oldComment: aString stamp: aStamp
+ 	oldComment := aString.
+ 	oldStamp := aStamp!

Item was added:
+ ----- Method: DSMethodSelectorChange>>newName (in category 'accessing') -----
+ newName
+ 	^ selector!

Item was added:
+ ----- Method: DSClassSuperclassChange class>>className:superclassName:instVarNames:classVarNames:poolDictionaryNames:category:type:classInstVarNames:comment:stamp:oldSuperclassName: (in category 'instance creation') -----
+ className: aClassName
+ superclassName: superclassName
+ instVarNames: instVarNames
+ classVarNames: classVarNames
+ poolDictionaryNames: poolDictionaryNames
+ category: aCategory
+ type: typeOfClass
+ classInstVarNames: metaInstVarNames
+ comment: classComment
+ stamp: commentStamp
+ oldSuperclassName: oldSuperclassName
+ 						
+ 	^(self className: aClassName)
+ 		superclassName: superclassName;
+ 		instVarNames: instVarNames;
+ 		classVarNames: classVarNames;
+ 		poolDictionaryNames: poolDictionaryNames;
+ 		category: aCategory;
+ 		type: typeOfClass;
+ 		classInstVarNames: metaInstVarNames;
+ 		comment: classComment;
+ 		stamp: commentStamp;
+ 		oldSuperclassName: oldSuperclassName;
+ 		yourself
+ !

Item was added:
+ ----- Method: DSMethodSelectorChange>>oldName (in category 'accessing') -----
+ oldName
+ 	^ oldSelector!

Item was changed:
  ----- Method: DSMethodSourceChange>>oldMethod: (in category 'accessing') -----
  oldMethod: aCompiledMethod
+ 	self oldSource: aCompiledMethod getSource asString.
- 	self oldSource: (self sourceFromMethod: aCompiledMethod).
  	self oldStamp: aCompiledMethod timeStamp.!

Item was added:
+ ----- Method: DSChangeSequence>>remove: (in category 'accessing') -----
+ remove: aChange
+ 
+ 	^ self changes remove: aChange!

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

Item was changed:
  ----- Method: DSDelta>>initialize (in category 'initialize-release') -----
  initialize
  	super initialize.
  	changeSequence := DSChangeSequence new.
- 	changeCounter := 0.
  	uuid := UUID new!

Item was added:
+ ----- Method: DSDelta>>add: (in category 'changes') -----
+ add: aChange
+ 
+ 	self changes add: aChange.
+ 	self grouper ifNotNil: [self grouper add: aChange].
+ 	self changed: #changeList.
+ 	^ aChange!

Item was added:
+ ----- Method: DSMethodChange>>className: (in category 'accessing') -----
+ className: aString
+ 	"Based on the name we figure out if this is a meta change."
+ 
+ 	^(aString endsWith: ' class')
+ 		ifTrue: [self meta: true. super className: (aString copyUpTo: Character space)]
+ 		ifFalse: [self meta: false. super className: aString]!

Item was added:
+ ----- Method: DSClassCommentChange class>>className:superclassName:instVarNames:classVarNames:poolDictionaryNames:category:type:classInstVarNames:comment:stamp:oldComment:oldStamp: (in category 'as yet unclassified') -----
+ className: aClassName
+ superclassName: superclassName
+ instVarNames: instVarNames
+ classVarNames: classVarNames
+ poolDictionaryNames: poolDictionaryNames
+ category: aCategory
+ type: typeOfClass
+ classInstVarNames: metaInstVarNames
+ comment: classComment
+ stamp: commentStamp
+ oldComment: oldComment
+ oldStamp: oldStamp
+ 						
+ 	^(self className: aClassName)
+ 		superclassName: superclassName;
+ 		instVarNames: instVarNames;
+ 		classVarNames: classVarNames;
+ 		poolDictionaryNames: poolDictionaryNames;
+ 		category: aCategory;
+ 		type: typeOfClass;
+ 		classInstVarNames: metaInstVarNames;
+ 		comment: classComment;
+ 		stamp: commentStamp;
+ 		oldComment: oldComment;
+ 		oldStamp: oldStamp;
+ 		yourself
+ !

Item was added:
+ ----- Method: DSDelta>>className:changeClass:superclassName:instVarNames:classVarNames:poolDictionaryNames:category:type:classInstVarNames:comment:stamp: (in category 'building') -----
+ className: className
+ changeClass: changeClassOrName
+ superclassName: superclassName
+ instVarNames: instVarNames
+ classVarNames: classVarNames
+ poolDictionaryNames: poolDictionaryNames
+ category: category
+ type: typeOfClass
+ classInstVarNames: classInstVarNames
+ comment: comment
+ stamp: stamp
+ 	"Create and return a class change.
+ 	It is not added to the Delta."
+ 
+ 	^(self getClass: changeClassOrName)
+ 		className: className
+ 		superclassName: superclassName
+ 		instVarNames: instVarNames
+ 		classVarNames: classVarNames
+ 		poolDictionaryNames: poolDictionaryNames
+ 		category: category
+ 		type: typeOfClass
+ 		classInstVarNames: classInstVarNames
+ 		comment: comment
+ 		stamp: stamp!

Item was changed:
  DSClassChange subclass: #DSClassCreatedChange
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'DeltaStreams-Model-Class'!
  
+ !DSClassCreatedChange commentStamp: 'gk 8/5/2009 23:56' prior: 0!
- !DSClassCreatedChange commentStamp: 'mtf 9/12/2007 11:12' prior: 0!
- This action must hold all information that is mandatory to supply in order to create a class - which means quite a lot of fields.
- When we later change a class (the DSClassChanged* classes) we are much more fine granular.
- 
  Note that this change only creates the class - it does not add methods or a class comment. See DSCompositeClassAddedChange.!

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

Item was added:
+ ----- Method: DSClassChange class>>tiradeClassName:superclassName:instVarNames:classVarNames:poolDictionaryNames:category:type:classInstVarNames:comment:stamp: (in category 'instance creation') -----
+ tiradeClassName: aClassName
+ superclassName: superclassName
+ instVarNames: instVarNames
+ classVarNames: classVarNames
+ poolDictionaryNames: poolDictionaryNames
+ category: aCategory
+ type: typeOfClass
+ classInstVarNames: metaInstVarNames
+ comment: classComment
+ stamp: commentStamp
+ 	"Instantiate a class change from a Tirade message."
+ 						
+ 	^(self tiradeClassName: aClassName)
+ 		tiradeSuperclassName: superclassName;
+ 		tiradeInstVarNames: instVarNames;
+ 		tiradeClassVarNames: classVarNames;
+ 		tiradePoolDictionaryNames: poolDictionaryNames;
+ 		tiradeCategory: aCategory;
+ 		tiradeType: typeOfClass;
+ 		tiradeClassInstVarNames: metaInstVarNames;
+ 		tiradeComment: classComment;
+ 		tiradeStamp: commentStamp;
+ 		yourself!

Item was added:
+ ----- Method: DSMethodSelectorChange>>fromChange: (in category 'initialize-release') -----
+ fromChange: aChange
+ 
+ 	super fromChange: aChange.
+ 	self oldSelector: aChange oldSelector.!

Item was changed:
  ----- Method: DSAnnotatedObject>>timeStamp: (in category 'accessing') -----
  timeStamp: aTimeStamp
+ 	self propertyAt: #timeStamp put: aTimeStamp printString!
- 	timeStamp := aTimeStamp!

Item was added:
+ ----- Method: DSMethodChange>>isOrphanIn: (in category 'testing') -----
+ isOrphanIn: environment
+ 	^ (super isOrphanIn: environment)
+ 		or: [((self getClassFrom: environment) includesSelector: self selector) not]!

Item was added:
+ ----- Method: DSMethodSelectorChange>>newSelector: (in category 'accessing') -----
+ newSelector: aString
+ 	self selector: aString!

Item was changed:
  DSAnnotatedObject subclass: #DSDelta
+ 	instanceVariableNames: 'uuid changeSequence'
- 	instanceVariableNames: 'changes uuid changeCounter changeSequence'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'DeltaStreams-Model-Base'!
  
+ !DSDelta commentStamp: 'gk 9/2/2009 19:02' prior: 0!
+ A Delta is much like a ChangeSet but improved and simplified. It can capture changes like a ChangeSet does (see #event:), but unlike ChangeSets multiple Deltas can be logging changes at the same time. A Delta maintains an ordered collection of change objects that is a true log unlike a ChangeSet which tries to normalize changes on the fly and does not maintain an order.
- !DSDelta commentStamp: 'gk 6/30/2009 00:12' prior: 0!
- A Delta is much like a ChangeSet but improved and simplified. It can capture changes like a ChangeSet does (see #event:), but unlike ChangeSets multiple Deltas can be logging changes at the same time. A Delta maintains a chronologically ordered collection of change objects that is a true log unlike a ChangeSet which tries to normalize changes on the fly and does not maintain an order.
  
  Also - each change object carries more information than a record in a ChangeSet does - and they know how to produce their anti change which in turn gives a Delta the ability to produce its own anti Delta. Such an anti Delta can be used to revert a Delta.
  
  Instance variables:
  
  changeSequence - an instance of DSChangeSequence.
  uuid - created when I am first instantiated, never changed.
- changeCounter - a counter to ensure strict sorting of changes, timestamps are not sufficient.
  
  Standard properties:
  
  #revertable - if missing we presume true. Can be used to explicitly flag a Delta as revertable/not revertable.
  !

Item was added:
+ ----- Method: DSMethodChange>>printOn: (in category 'printing') -----
+ printOn: aStream
+ 	aStream nextPutAll: self className.
+ 	self isMeta ifTrue: [aStream nextPutAll: ' class'].
+ 	aStream
+ 		nextPutAll: '>>';
+ 		nextPutAll: self selector asString;
+ 		space; nextPutAll: self action!

Item was removed:
- ----- Method: DSBasicClassChange>>classGroupKey (in category 'grouping') -----
- classGroupKey
- 	"See the comment in DSChange>>inClassGroupFor:"
- 	^ DSBasicClassChange fromChange: self!

Item was removed:
- ----- Method: DSBasicMethodChange>>fromClass:selector: (in category 'initialize-release') -----
- fromClass: aClass selector: aSelector
- 	self class: aClass selector: aSelector!

Item was removed:
- ----- Method: DSCompositeMethodChange>>selector (in category 'accessing') -----
- selector
- 	^ self changes last selector!

Item was removed:
- ----- Method: DSClassSuperclassChange class>>class:from:to: (in category 'as yet unclassified') -----
- class: aClass from: oldSuperclass to: newSuperclass
- 	^(self class: aClass) oldSuperclass: oldSuperclass; newSuperclass: newSuperclass; yourself!

Item was removed:
- DSChangeSequence subclass: #DSCompositeMethodChange
- 	instanceVariableNames: 'protocol'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'DeltaStreams-Model-Composite'!

Item was removed:
- ----- Method: DSDelta>>isLogging (in category 'change logging') -----
- isLogging
- 	"Is this Delta logging system changes?"
- 
- 	^SystemChangeNotifier uniqueInstance hasNotificationsFor: self!

Item was removed:
- ----- Method: DSDelta>>buildGrouper (in category 'accessing') -----
- buildGrouper
- 
- 	^self propertyAt: #grouper put: (DSGroupedClassChange withAll: self; yourself)!

Item was removed:
- ----- Method: DSMethodNameChange>>oldSelector (in category 'accessing') -----
- oldSelector
- 	^ oldSelector!

Item was removed:
- ----- Method: DSClassCommentChange class>>changing:from:to:oldStamp:newStamp: (in category 'as yet unclassified') -----
- changing: aClass from: oldComment to: newComment oldStamp: oldStamp newStamp: newStamp
- 	^(self fromClass: aClass)
- 		oldComment: oldComment;
- 		newComment: newComment;
- 		oldStamp: oldStamp;
- 		newStamp: newStamp;
- 		yourself!

Item was removed:
- ----- Method: DSClassTypeChange class>>changing:from:to: (in category 'as yet unclassified') -----
- changing: aClass from: old to: new
- 	^ (self fromClass: aClass)
- 		oldType: old;
- 		newType: new;
- 		yourself!

Item was removed:
- ----- Method: DSChange>>isRecord (in category 'testing') -----
- isRecord
- 	^false!

Item was removed:
- ----- Method: DSMethodNameChange>>newSelector (in category 'accessing') -----
- newSelector
- 	^ selector!

Item was removed:
- ----- Method: DSClassRemovedChange class>>fromClass: (in category 'instance creation') -----
- fromClass: aClass 
- 	"A class was removed from the system. If aClass
- 	has methods we need to do create a composite delete change,
- 	otheriwse this class change is enough."
- 
- 	(aClass theNonMetaClass selectors isEmpty and: [aClass theMetaClass selectors isEmpty])
- 		ifTrue: [ ^ super fromClass: aClass]
- 		ifFalse: [ ^ DSCompositeClassDeletedChange fromClass: aClass]!

Item was removed:
- ----- Method: DSMethodNameChange>>isName (in category 'testing') -----
- isName
- 	^true!

Item was removed:
- ----- Method: DSBasicClassChange>>setClass: (in category 'accessing') -----
- setClass: aClass
- 	self className: aClass theNonMetaClass name!

Item was removed:
- ----- Method: DSBasicMethodChange>>selector: (in category 'accessing') -----
- selector: aString
- 	selector := aString asSymbol!

Item was removed:
- ----- Method: DSChange>>inMergeGroupFor: (in category 'grouping') -----
- inMergeGroupFor: aChange
- "See the comment in #inMergeGroupFor:withClassName:"
- 	| myKey otherKey |
- 	myKey := self mergeGroupKey ifNil: [^ false].
- 	otherKey := aChange mergeGroupKey ifNil: [^ false].
- 	^ myKey = otherKey!

Item was removed:
- ----- Method: DSBasicMethodChange>>hash (in category 'comparing') -----
- hash
- "This is just for comparing of group keys. See the comment in #=."
- 	^ (super hash bitXor: meta hash) bitXor: selector hash!

Item was removed:
- ----- Method: DSBasicMethodChange>>isMethodChange (in category 'testing') -----
- isMethodChange
- 	^ true!

Item was removed:
- ----- Method: DSBasicMethodChange>>name: (in category 'accessing') -----
- name: aSymbol
- 	selector := aSymbol!

Item was removed:
- ----- Method: DSDelta>>addChange: (in category 'change logging') -----
- addChange: aChange
- 	"Within a Delta we give a change a monotonically increasing number
- 	in order to be able to sort changes chronologically. The TimeStamp does
- 	not work if changes are created very fast, they end up the same and sorting
- 	becomes undefined. The change is copied if it already has a number,
- 	in that case it is already in a different delta and we do not want to share."
- 
- 	| change |
- 	change := aChange number ifNil: [aChange] ifNotNil: [aChange copy].
- 	change number: self incrementChangeCounter.
- 	self changes add: change.
- 	self grouper ifNotNil: [self grouper add: change].
- 	self changed: #changeList.
- 	^ change!

Item was removed:
- ----- Method: DSChange>>inMethodGroupFor:withClassName: (in category 'grouping') -----
- inMethodGroupFor: aChange withClassName: className
- "Answers true if I am in the same method group as aChange. I answer true on two conditions: Either:
- 	1. both aChange and I are method changes, and we are both part of the same class or metaclass and have the same selector, or
- 	2. both aChange and I are class changes, are not method changes, and are part of the same class/metaclass pair
- 	
- As in #inClassGroupFor:withClassName:, aChange is treated as having the given name rather its real name to work around class renames"
- 	| myKey otherKey |
- 	myKey := self methodGroupKey ifNil: [^ false].
- 	otherKey := aChange methodGroupKey ifNil: [^ false].
- 	^ myKey = (otherKey className: className)!

Item was removed:
- ----- Method: DSBasicMethodChange>>class:selector: (in category 'initialize-release') -----
- class: aClass selector: aSelector
- 	self setClass: aClass.
- 	self selector: aSelector!

Item was removed:
- ----- Method: DSClassChange>>mergeGroupKey (in category 'grouping') -----
- mergeGroupKey
- "See the comment in DSDelta>>inMergeGroupFor:. My instances are asymmetric and cannot be merged, so return nil"
- 	^ nil!

Item was removed:
- ----- Method: DSBasicMethodChange>>name (in category 'accessing') -----
- name
- 	^ selector!

Item was removed:
- ----- Method: DSMethodNameChange>>newName: (in category 'accessing') -----
- newName: aString
- 	self selector: aString!

Item was removed:
- ----- Method: DSClassCategoryChange class>>className:from:to: (in category 'as yet unclassified') -----
- className: aName from: oldCategory to: newCategory
- 	^(self className: aName)
- 		oldCategory: oldCategory;
- 		newCategory: newCategory;
- 		yourself!

Item was removed:
- ----- Method: DSMethodNameChange>>oldName: (in category 'accessing') -----
- oldName: aString
- 	oldSelector := aString asSymbol!

Item was removed:
- ----- Method: DSCompositeMethodChange>>protocol (in category 'accessing') -----
- protocol
- 	protocol ifNotNil: [^ protocol].
- 	Smalltalk at: self className ifPresent: [:aClass |
- 		^ aClass organization categoryOfElement: self selector].
- 	^ Categorizer default!

Item was removed:
- ----- Method: DSCompositeMethodChange>>className (in category 'accessing') -----
- className
- 	^ self changes last className!

Item was removed:
- ----- Method: DSMethodNameChange>>oldName (in category 'accessing') -----
- oldName
- 	^ oldSelector!

Item was removed:
- ----- Method: DSBasicMethodChange>>fromChange: (in category 'initialize-release') -----
- fromChange: aChange
- 	super fromChange: aChange.
- 	self className: aChange className.
- 	self selector: aChange selector.
- 	self meta: aChange meta.!

Item was removed:
- ----- Method: DSMethodNameChange>>isMethodName (in category 'testing') -----
- isMethodName
- 	^true!

Item was removed:
- ----- Method: DSCompositeMethodChange>>applyUsing: (in category 'applying') -----
- applyUsing: anApplier
- 	^ anApplier applyCompositeMethodChange: self!

Item was removed:
- ----- Method: DSCompositeMethodChange>>add: (in category 'accessing') -----
- add: aChange
- 	aChange isMethodChange ifFalse: [^ nil].
- 	aChange isMethodAdded | aChange isMethodRemoved ifTrue: [protocol := aChange protocol].
- 	aChange isMethodProtocol ifTrue: [protocol := aChange newProtocol].
- 	^ super add: aChange!

Item was removed:
- ----- Method: DSDelta>>incrementChangeCounter (in category 'private') -----
- incrementChangeCounter
- 	"Monotonically increasing change counter to enable strict chronological sorting.
- 	And no, we can't rely on the collection size - because changes may have been removed
- 	causing holes in the sequence etc."
- 
- 	^changeCounter := changeCounter + 1!

Item was removed:
- ----- Method: DSBasicClassChange class>>class: (in category 'instance creation') -----
- class: aClass
- 	^ self new
- 		setClass: aClass;
- 		yourself!

Item was removed:
- DSMethodChange subclass: #DSMethodNameChange
- 	instanceVariableNames: 'oldSelector'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'DeltaStreams-Model-Method'!

Item was removed:
- ----- Method: DSMethodNameChange>>fromChange: (in category 'initialize-release') -----
- fromChange: aChange
- 
- 	super fromChange: aChange.
- 	self oldSelector: aChange oldSelector.!

Item was removed:
- ----- Method: DSSystemEditorApplier>>applyMethodSnapshot: (in category 'as yet unclassified') -----
- applyMethodSnapshot: snapshot
- 	"Snapshots just record the old version; there is no new version. So, only apply them if there is nothing better."
- 	(self classEditorForChange: snapshot)
- 		edMethodAt: snapshot selector ifAbsent: [self applyMethodAdded: snapshot]!

Item was removed:
- ----- Method: DSChange>>inClassGroupFor: (in category 'grouping') -----
- inClassGroupFor: aChange
- "Answers true if I am an the same class as aChange, false otherwise"
- 	| myKey otherKey |
- 	myKey := self classGroupKey ifNil: [^ false].
- 	otherKey := aChange classGroupKey ifNil: [^ false].
- 	^ myKey = otherKey!

Item was removed:
- DSBasicClassChange subclass: #DSBasicMethodChange
- 	instanceVariableNames: 'selector meta'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'DeltaStreams-Model-Method'!
- 
- !DSBasicMethodChange commentStamp: 'gk 8/28/2007 22:46' prior: 0!
- An abstract super class for all actions affecting a specific method:
- 
- selector: (Symbol) the method selector
- className: (Symbol) the name of the defining class
- metaclass: (Boolean) true if defined on the metaclass, false if defined on the class!

Item was removed:
- ----- Method: DSChange>>inClassGroupFor:withClassName: (in category 'grouping') -----
- inClassGroupFor: aChange withClassName: className
- "Answers true if I am an the same class as aChange, false otherwise. For the purposes of comparison, aChange is assumed to have the given class name rather than its actual class name to work around renaming issues"
- 	| myKey otherKey |
- 	myKey := self classGroupKey ifNil: [^ false].
- 	otherKey := aChange classGroupKey ifNil: [^ false].
- 	^ myKey = (otherKey className: className)!

Item was removed:
- ----- Method: DSCompositeMethodChange>>isClassChange (in category 'testing') -----
- isClassChange
- 	^ true!

Item was removed:
- ----- Method: DSBasicMethodChange>>meta: (in category 'accessing') -----
- meta: aBoolean
- 
- 	meta := aBoolean!

Item was removed:
- ----- Method: DSDelta>>asAntiChange (in category 'applying') -----
- asAntiChange
- 	"Return a new Delta that, when applied, reverts each change of this Delta
- 	in reverse order. Each change should have enough information to create
- 	an anti change from itself."
- 
- 	| anti |
- 	self isRevertable ifFalse: [DSDeltaNotRevertableException signal].
- 	anti := DSDelta name: 'undo ' translated, self name.
- 	self propertiesDo: [:key :val | anti propertyAt: key put: val]. 
- 	self changes reverseDo: [:each | anti addChange: each asAntiChange]. 
- 	^anti!

Item was removed:
- ----- Method: DSCompositeMethodChange>>isMethodChange (in category 'testing') -----
- isMethodChange
- 	^ true!

Item was removed:
- ----- Method: DSMethodNameChange>>applyUsing: (in category 'applying') -----
- applyUsing: anApplier
- 	^ anApplier applyMethodName: self!

Item was removed:
- ----- Method: DSBasicMethodChange>>isMeta (in category 'testing') -----
- isMeta
- 	^ meta!

Item was removed:
- ----- Method: DSChange>>number (in category 'accessing') -----
- number
- 	^number!

Item was removed:
- ----- Method: DSCompositeMethodChange>>category (in category 'accessing') -----
- category
- 	"for compatability with DSChangeClassifier, letting it implement the Categorization protocol"
- 	^ self protocol!

Item was removed:
- ----- Method: DSCompositeMethodChange>>fromChange: (in category 'initialize-release') -----
- fromChange: aChange
- 
- 	super fromChange: aChange.
- 	protocol := aChange protocol!

Item was removed:
- ----- Method: DSBasicMethodChange>>= (in category 'comparing') -----
- = aChange
- "This is just for comparing of group keys. See the comment in DSClassChange>>=.
- 
- Group keys for method changes depend on the class/metaclass separation and the selector, in addition to what is required for class changes to group together"
- 	^ super = aChange and: [meta == aChange meta] and: [selector == aChange selector]!

Item was removed:
- ----- Method: DSChange>><= (in category 'comparing') -----
- <= other
- 	"Sort by number per default, this represents order of addition."
- 
- 	^number <= other number!

Item was removed:
- ----- Method: DSMethodNameChange>>newName (in category 'accessing') -----
- newName
- 	^ selector!

Item was removed:
- ----- Method: DSBasicMethodChange class>>fromClass:selector: (in category 'instance creation') -----
- fromClass: aClass selector: selector
- 	^ self new fromClass: aClass selector: selector; yourself!

Item was removed:
- ----- Method: DSVisitor>>applyCategorizedCompositeChange: (in category 'composite changes') -----
- applyCategorizedCompositeChange: change
- 	"Treat like a composite change by default"
- 	
- 	^ self applyCompositeChange: change!

Item was removed:
- ----- Method: DSClassSuperclassChange class>>className:fromName:toName: (in category 'as yet unclassified') -----
- className: aName fromName: oldSuperclassName toName: newSuperclassName
- 	^(self className: aName) oldSuperclassName: oldSuperclassName; newSuperclassName: newSuperclassName; yourself!

Item was removed:
- ----- Method: DSMethodProtocolChange class>>class:selector:from:to: (in category 'as yet unclassified') -----
- class: aClass selector: selector from: oldProtocol to: newProtocol
- 	^ (self class: aClass selector: selector)
- 		oldProtocol: oldProtocol;
- 		newProtocol: newProtocol;
- 		yourself!

Item was removed:
- ----- Method: DSChange>>classGroupKey (in category 'grouping') -----
- classGroupKey
- "see the comment in #inClassGroupFor:. Changes are not groupable by default, so return nil"
- 	^ nil!

Item was removed:
- ----- Method: DSDelta>>stopLogging (in category 'change logging') -----
- stopLogging
- 	"Make this Delta stop logging system changes.
- 	ChangeSets only have one that is logging."
- 
- 	self isLogging ifTrue: [
- 		SystemChangeNotifier uniqueInstance noMoreNotificationsFor: self]!

Item was removed:
- ----- Method: DSBasicMethodChange>>meta (in category 'accessing') -----
- meta
- 	^ meta!

Item was removed:
- ----- Method: DSBasicMethodChange>>sourceFromMethod: (in category 'convenience') -----
- sourceFromMethod: aCompiledMethod
- 	^ aCompiledMethod getSourceFor: self selector in: self getClass!

Item was removed:
- ----- Method: DSBasicMethodChange>>className: (in category 'accessing') -----
- className: aString
- 	^ (aString endsWith: ' class')
- 		ifTrue: [self meta: true. super className: (aString copyUpTo: Character space)]
- 		ifFalse: [self meta ifNil: [self meta: false]. super className: aString]!

Item was removed:
- ----- Method: DSDelta>>fixChangeNumbers (in category 'utilities') -----
- fixChangeNumbers
- 	"Fix the change numbers to conform to the invariant that the number
- 	of the change is the same as it's index in the change collection."
- 
- 	| chgs |
- 	chgs := self changes.
- 	chgs withIndexDo: [:change :index | change number: index].
- 	changeCounter := chgs size!

Item was removed:
- ----- Method: DSMethodChange>>mergeGroupKey (in category 'grouping') -----
- mergeGroupKey
- "See the comment in DSDelta>>inMergeGroupFor:. My instances are not symetric enough to be mergable, so return nil"
- 	^ nil!

Item was removed:
- ----- Method: DSBasicMethodChange>>selector (in category 'accessing') -----
- selector
- 	^ selector!

Item was removed:
- ----- Method: DSMethodNameChange>>newSelector: (in category 'accessing') -----
- newSelector: aString
- 	self selector: aString!

Item was removed:
- ----- Method: DSBasicMethodChange>>setClass: (in category 'convenience') -----
- setClass: aClass
- 	super setClass: aClass.
- 	self meta: aClass isMeta!

Item was removed:
- ----- Method: DSCompositeMethodChange>>isMeta (in category 'accessing') -----
- isMeta
- 	^ self changes last isMeta!

Item was removed:
- ----- Method: DSMethodNameChange>>asAntiChange (in category 'anti') -----
- asAntiChange
- 	^ super asAntiChange
- 		oldSelector: selector;
- 		newSelector: oldSelector;
- 		yourself!

Item was removed:
- ----- Method: DSBasicMethodChange class>>class:selector: (in category 'instance creation') -----
- class: aClass selector: selector
- 	^ (self class: aClass)
- 		selector: selector;
- 		yourself!

Item was removed:
- ----- Method: DSBasicMethodChange>>isOrphanIn: (in category 'validation') -----
- isOrphanIn: environment
- 	^ (super isOrphanIn: environment)
- 		or: [((self getClassFrom: environment) includesSelector: self selector) not]!

Item was removed:
- ----- Method: DSChange>>number: (in category 'accessing') -----
- number: aNumber
- 	number := aNumber!

Item was removed:
- ----- Method: DSBasicMethodChange>>methodGroupKey (in category 'grouping') -----
- methodGroupKey
- "For grouping. See the comment in DSChange>>inMethodGroupFor:"
- 	^ DSBasicMethodChange fromChange: self!

Item was removed:
- ----- Method: DSBasicMethodChange>>printOn: (in category 'as yet unclassified') -----
- printOn: aStream
- 	aStream nextPutAll: self className.
- 	self isMeta ifTrue: [aStream nextPutAll: ' class'].
- 	aStream
- 		nextPutAll: '>>';
- 		nextPutAll: self selector;
- 		space; nextPutAll: self action!

Item was removed:
- ----- Method: DSMethodSourceChange class>>class:selector:from:to: (in category 'as yet unclassified') -----
- class: aClass selector: selector from: oldMethod to: newMethod
- 	^ (self class: aClass selector: selector)
- 		oldMethod: oldMethod;
- 		newMethod: newMethod;
- 		yourself!

Item was removed:
- ----- Method: DSChange>>inMergeGroupFor:withClassName: (in category 'grouping') -----
- inMergeGroupFor: aChange withClassName: className
- "Answers true if both aChange and I:
- 	1. are primitive changes (ie not composite)
- 	2. are of the same class
- 	3. are non-shadowing changes
- 	4. satisfy all the conditions listed in the comment of #inMethodGroupFor:withClassName:
- 	
- As in #inClassGroupFor:withClassName:, aChange is treated as having the given name rather its real name to work around class renames
- 
- If I answer true, aChange and I can be merged into a single change, though not necesarilly cleanly. Shadowing changes (additions and removals) do not have the before/after symmetry required to be in this equivilance group"
- 	| myKey otherKey |
- 	myKey := self mergeGroupKey ifNil: [^ false].
- 	otherKey := aChange mergeGroupKey ifNil: [^ false].
- 	^ myKey = (otherKey className: className)!

Item was removed:
- ----- Method: DSBasicClassChange>>methodGroupKey (in category 'grouping') -----
- methodGroupKey
- 	"See the comment in DSChange>>inMethodGroupFor:"
- 	^ self classGroupKey!

Item was removed:
- ----- Method: DSClassSuperclassChange class>>changing:from:to: (in category 'as yet unclassified') -----
- changing: aClass from: oldSuperclass to: newSuperclass
- 	^(self fromClass: aClass)
- 		oldSuperclass: oldSuperclass;
- 		newSuperclass: newSuperclass;
- 		yourself!

Item was removed:
- ----- Method: DSChange>>methodGroupKey (in category 'grouping') -----
- methodGroupKey
- "see the comment in #inMethodGroupFor:. Changes are not groupable by default, so return nil"
- 	^ nil!

Item was removed:
- ----- Method: DSClassChange class>>className: (in category 'instance creation') -----
- className: aClassName
- 	^self new className: aClassName; yourself!

Item was removed:
- ----- Method: DSMethodNameChange class>>class:selector:from:to: (in category 'as yet unclassified') -----
- class: aClass selector: selector from: oldSelector to: newSelector
- 	^ (self class: aClass selector: selector)
- 		newSelector: newSelector;
- 		yourself!

Item was removed:
- ----- Method: DSBasicClassChange>>mergeGroupKey (in category 'grouping') -----
- mergeGroupKey
- "See the comment in DSChange>>inMergeGroupFor: Creates a blank instance of this class; only className is set; all other vars are nil. This sends the class message to determine the class to create rather than using a well-known class, like class group key and method group key do. Thus, merge group keys are specific to the change type, rather than generic for all class changes"
- 	^ self class new className: className!

Item was removed:
- ----- Method: DSDelta>>startLogging (in category 'change logging') -----
- startLogging
- 	"Make this Delta start logging system changes.
- 	ChangeSets only have one that is logging."
- 
- 	self isLogging ifFalse: [
- 		SystemChangeNotifier uniqueInstance
- 			notify: self
- 			ofAllSystemChangesUsing: #event:]!

Item was removed:
- ----- Method: DSMethodNameChange>>oldSelector: (in category 'accessing') -----
- oldSelector: aString
- 	oldSelector := aString asSymbol!

Item was removed:
- ----- Method: DSClassCategoryChange class>>changing:from:to: (in category 'as yet unclassified') -----
- changing: aClass from: oldCategory to: newCategory
- 	^(self fromClass: aClass)
- 		oldCategory: oldCategory;
- 		newCategory: newCategory;
- 		yourself!

Item was removed:
- ----- Method: DSChange>>inMethodGroupFor: (in category 'grouping') -----
- inMethodGroupFor: aChange
- "See the comment in #inMethodGroupFor:withClassChange: for the meaning of this method"
- 	| myKey otherKey |
- 	myKey := self methodGroupKey ifNil: [^ false].
- 	otherKey := aChange methodGroupKey ifNil: [^ false].
- 	^ myKey = otherKey!

Item was removed:
- ----- Method: DSChange>>mergeGroupKey (in category 'grouping') -----
- mergeGroupKey
- "see the comment in #inMergeGroupFor:. Changes are not groupable by default, so return nil"
- 	^ nil!



More information about the Packages mailing list