[Pkg] DeltaStreams: DeltaStreams-Deprecated-gk.4.mcz

squeak-dev-noreply at lists.squeakfoundation.org squeak-dev-noreply at lists.squeakfoundation.org
Thu Sep 3 14:26:14 UTC 2009


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

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

Name: DeltaStreams-Deprecated-gk.4
Author: gk
Time: 3 September 2009, 4:25:52 pm
UUID: 38b0222f-d09e-45ce-b178-d0e7cd84358d
Ancestors: DeltaStreams-Deprecated-gk.3

Removals.

=============== Diff against DeltaStreams-Deprecated-gk.3 ===============

Item was changed:
  ----- Method: DSDeltaEditor>>comment:stamp: (in category 'editing') -----
  comment: aComment stamp: aStamp
  
  	class ifNotNil: [
  		^delta commentClass: class
+ 			from: class organization classComment asString
- 			from: class organization classComment
  			to: aComment
  			oldStamp: class organization commentStamp
  			newStamp: aStamp]
  		ifNil: [
  		^delta commentClassName: className
  			from: ''
  			to: aComment
  			oldStamp: nil
  			newStamp: aStamp]!

Item was changed:
  ----- Method: DSDeltaEditor>>createClassName: (in category 'editing') -----
  createClassName: aName
  	"Add an existing class."
  
  	className := aName.
+ 	^delta add: (DSClassCreatedChange className: className)!
- 	^delta addChange: (DSClassCreatedChange className: className)!

Item was removed:
- ----- Method: DSChangeCategorizer class>>forMethods (in category 'as yet unclassified') -----
- forMethods
- 	^ self
- 		default: [:aSymbol | DSCompositeMethodChange  new]
- 		classify: [:aChange | aChange selector]!

Item was removed:
- ----- Method: DSGroupedClassChange>>do: (in category 'enumerating') -----
- do: aBlock
- 	super do: aBlock.
- 	self methodChanges do: aBlock.
- 	self classMethodChanges do: aBlock!

Item was removed:
- ----- Method: DSChangeCategorizer>>groupsDo: (in category 'enumerating') -----
- groupsDo: aBlock
- 	self dictionary do: [:ea | ea groupsDo: aBlock]!

Item was removed:
- ----- Method: DSGroupedClassChange>>classMethodChanges (in category 'accessing') -----
- classMethodChanges
- 	^ classMethodChanges 
- 		ifNil: [classMethodChanges := DSChangeCategorizer forMethods]!

Item was removed:
- ----- Method: DSClassRecord>>initializeFrom: (in category 'initialize-release') -----
- initializeFrom: aClass
- 	super initializeFrom: aClass.
- 	classInstVarNames := aClass class instVarNames.
- 	comment := aClass organization classComment.
- 	stamp := aClass organization commentStamp.!

Item was removed:
- ----- Method: DSSystemEditorMarker>>editor: (in category 'initialize-release') -----
- editor: aSystemEditor
- 
- 	editor := aSystemEditor!

Item was removed:
- ----- Method: DSGroupedClassChange>>add: (in category 'accessing') -----
- add: aChange
- 	aChange isMethodChange ifTrue: [^ self addMethodChange: aChange].
- 	^ super add: aChange!

Item was removed:
- ----- Method: DSChangeCategorizer>>keys (in category 'accessing') -----
- keys
- 	^ self dictionary keys!

Item was removed:
- ----- Method: DSSystemEditorMarker>>applyClassVarsChanged: (in category 'class changes') -----
- applyClassVarsChanged: change
- 	"Changed class vars, we ignore ordering as it is irrelevant - 
- 	they are actually kept in a Dictionary."
- 
- 	| classEditor |
- 	classEditor := self classEditorForChange: change.
- 	change added do: [:each | classEditor addClassVarName: each].
- 	change removed do: [:each | classEditor removeClassVarName: each]!

Item was removed:
- ----- Method: DSClassRecord>>asAntiChange (in category 'anti') -----
- asAntiChange
- 	^ self copy!

Item was removed:
- ----- Method: DSMethodRecord>>asAntiChange (in category 'anti') -----
- asAntiChange
- 	^ self!

Item was removed:
- ----- Method: DSSystemEditorMarker>>ensureSharedPools: (in category 'private') -----
- ensureSharedPools: anArray
- 	anArray do: [:name | Smalltalk at: name asSymbol ifAbsentPut: [Dictionary new]]!

Item was removed:
- ----- Method: DSGroupedClassChange>>groupsDo: (in category 'enumerating') -----
- groupsDo: aBlock
- 	super groupsDo: aBlock.
- 	self methodChanges groupsDo: aBlock.
- 	self classMethodChanges groupsDo: aBlock!

Item was removed:
- ----- Method: DSSystemEditorMarker>>applyMethodRemoved: (in category 'method changes') -----
- applyMethodRemoved: change
- 	"remove a method from a class. Does nothing if class does not exist."
- 	
- 	| classEditor |
- 	classEditor := editor at: change className ifAbsent: [^ self].
- 	change isMeta ifTrue: [classEditor := classEditor class].
- 	classEditor removeSelector: change selector!

Item was removed:
- ----- Method: DSSystemEditorMarker>>applyClassRemoved: (in category 'class changes') -----
- applyClassRemoved: change
- 	"Remove a class. Do nothing if it isn't there'"
- 
- 	| classEditor |
- 	classEditor := editor at: change className ifAbsent: [^ self].
- 	classEditor removeFromSystem!

Item was removed:
- ----- Method: DSSystemEditorMarker>>applyClassSuperclassChanged: (in category 'class changes') -----
- applyClassSuperclassChanged: change
- 	"Changed a class superclass."
- 
- 	(self classEditorForChange: change)
- 		superclass: (editor at: change newSuperclassName ifAbsent: [editor at: #Object])!

Item was removed:
- ----- Method: DSSystemEditorMarker>>applySuperclassChanged: (in category 'class changes') -----
- applySuperclassChanged: change
- 	"Change the superclass of a class."
- 
- 	| classEditor superEditor |
- 	classEditor := editor ensureClassNamed: change className.
- 	superEditor := editor at: change newSuperclassName ifAbsent: [^ self].
- 	classEditor superclass: superEditor!

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

Item was removed:
- ----- Method: DSSystemEditorMarker class>>on: (in category 'as yet unclassified') -----
- on: aSystemEditor
- 	^ self new editor: aSystemEditor !

Item was removed:
- DSClassChange subclass: #DSClassRecord
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'DeltaStreams-Deprecated'!
- 
- !DSClassRecord commentStamp: 'mtf 9/12/2007 18:17' prior: 0!
- My instances are responsible for storing the state of the class if there is no other change that can do that. For example, if the only change in a delta is an inst var change, there is no way to get the old class comment. In that case, a record would be logged prior to the inst var change so that the other class data is in the delta. This is not a change.
- 
- A record can go in a Delta, and can be applied, but it should do nothing when applied, unless there is no other source available. So, it mostly serves as a marker in a stream of changes!

Item was removed:
- ----- Method: DSSystemEditorMarker>>applyMethodSourceChanged: (in category 'method changes') -----
- applyMethodSourceChanged: change
- 	"Apply a method source change. If class or method is missing, create and categorize under default category."
- 
- 	(self methodEditorForChange: change)
- 		source: change newSource;
- 		stamp: change newStamp!

Item was removed:
- ----- Method: DSChangeCategorizer>>add:classified: (in category 'accessing') -----
- add: aChange classified: aSymbol
- 	(self at: aSymbol) add: aChange.
- 	categorizer ifNotNil: [categorizer classify: aSymbol under: (self at: aSymbol) category].
- 	^ aChange!

Item was removed:
- ----- Method: DSChangeCategorizer>>dictionary (in category 'accessing') -----
- dictionary
- 	^ dict ifNil: [dict := Dictionary new]!

Item was removed:
- ----- Method: DSSystemEditorMarker>>applyClassCommentChanged: (in category 'class changes') -----
- applyClassCommentChanged: change
- 	"Changed a class comment."
- 
- 	(self classEditorForChange: change) classComment: change newComment stamp: change newStamp!

Item was removed:
- ----- Method: DSSystemEditorMarker>>methodEditorForChange: (in category 'private') -----
- methodEditorForChange: aMethodChange
- 	"answer the method editor for the change, creating a new, empty method if absent"
- 	
- 	| classEditor |
- 	classEditor := self classEditorForChange: aMethodChange.
- 	classEditor edMethodAt: aMethodChange selector ifAbsent: [classEditor
- 		compile: aMethodChange selector nullMethodSource
- 		classified: Categorizer default].
- 	^ classEditor edMethodAt: aMethodChange selector!

Item was removed:
- ----- Method: DSSystemEditorMarker>>applyClassNameChanged: (in category 'class changes') -----
- applyClassNameChanged: change
- 	"Changed a class name. If the old class does not exist, do nothing. If the new name already exists, the behavior is not implemented"
- 
- 	(editor includesKey: change oldName) ifFalse: [^ self].
- 	(editor includesKey: change newName) ifTrue: [^ self error: 'Class rename conflict. See the comment in DSDeltaDirtyApplyTest>>testClassRenameConfict'].
- 	(self classEditorForChange: change) rename: change newName.!

Item was removed:
- ----- Method: DSChangeCategorizer>>buildCategorizer (in category 'accessing') -----
- buildCategorizer
- 	| aCategorizer |
- 	aCategorizer := Categorizer defaultList: Array new.
- 	self dictionary keysAndValuesDo: [:name :group | aCategorizer classify: name under: group category].
- 	^ aCategorizer!

Item was removed:
- ----- Method: DSGroupedClassChange>>reverseDo: (in category 'enumerating') -----
- reverseDo: aBlock
- 	self classMethodChanges reverseDo: aBlock.
- 	self methodChanges reverseDo: aBlock.
- 	super reverseDo: aBlock.
- !

Item was removed:
- ----- Method: DSClassRecord>>classInstVarChange (in category 'convenience') -----
- classInstVarChange
- 	^ DSClassInstVarsChange className: className
- 		from: Array new
- 		to: classInstVarNames!

Item was removed:
- ----- Method: DSSystemEditorMarker>>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: DSChangeCategorizer>>at: (in category 'accessing') -----
- at: aSymbol
- 	^ self dictionary at: aSymbol ifAbsentPut: [defaultBlock value: aSymbol]!

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

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

Item was removed:
- ----- Method: DSSystemEditorMarker>>applyClassInstVarsChanged: (in category 'class changes') -----
- applyClassInstVarsChanged: change
- 	"Changed class instvars."
- 
- 	| classEditor |
- 	classEditor := self classEditorForChange: change.
- 	change added do: [:each | classEditor addInstVarName: each].
- 	change removed do: [:each | classEditor removeInstVarName: each].
- 	change moved notEmpty ifTrue: [
- 		classEditor rearrangeInstVarNames: change movedWithIndices]!

Item was removed:
- ----- Method: DSGroupedClassChange>>addMethodChange: (in category 'private') -----
- addMethodChange: aChange
- 	^ (aChange isMeta
- 		ifFalse: [self methodChanges]
- 		ifTrue: [self classMethodChanges]
- 	) add: aChange!

Item was removed:
- ----- Method: DSGroupedClassChange>>methodChanges (in category 'accessing') -----
- methodChanges
- 	^ methodChanges ifNil: [methodChanges := DSChangeCategorizer forMethods]!

Item was removed:
- ----- Method: DSSystemEditorMarker>>applyMethodProtocolChanged: (in category 'method changes') -----
- applyMethodProtocolChanged: change
- 	"Change the protocol of a method, Does nothing if either the class or the method don't exist'"
- 
- 	(self methodEditorForChange: change)
- 		category: change newProtocol!

Item was removed:
- ----- Method: DSSystemEditorMarker>>applyMethodAdded: (in category 'method changes') -----
- applyMethodAdded: change
- 	"Add a method to the class."
- 
- 	(self classEditorForChange: change)
- 		compile: change source
- 		classified: change protocol
- 		withStamp: change stamp
- 		notifying: nil
- 		logSource: true!

Item was removed:
- DSCompositeClassChange subclass: #DSGroupedClassChange
- 	instanceVariableNames: 'methodChanges classMethodChanges'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'DeltaStreams-Deprecated'!
- 
- !DSGroupedClassChange commentStamp: 'mtf 9/21/2007 12:55' prior: 0!
- My instances represent changes made to a specific class, grouped by method for easy lookup. This is especially useful when browsing a delta
- 
- I may be superceded by DSChangeCategorizer, but am still referenced. I may be removed in the future!

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

Item was removed:
- ----- Method: DSChangeCategorizer>>applyUsing: (in category 'applying') -----
- applyUsing: anApplier
- 	anApplier applyCategorizedCompositeChange: self!

Item was removed:
- ----- Method: DSChangeCategorizer>>do: (in category 'enumerating') -----
- do: aBlock
- 	self dictionary do: [:ea | ea do: aBlock]!

Item was removed:
- ----- Method: DSChangeCategorizer>>default:classify: (in category 'initialize-release') -----
- default: aDefaultBlock classify: aClassifyBlock
- 	defaultBlock := aDefaultBlock.
- 	classifyBlock := aClassifyBlock!

Item was removed:
- ----- Method: DSSystemEditorMarker>>classEditorForChange: (in category 'private') -----
- classEditorForChange: change
- 	| classEditor |
- 	classEditor := editor ensureClassNamed: change className.
- 	^ change isMeta
- 		ifTrue: [classEditor class]
- 		ifFalse: [classEditor].!

Item was removed:
- ----- Method: DSChangeCategorizer>>add: (in category 'accessing') -----
- add: aChange
- 	self add: aChange classified: (classifyBlock value: aChange).
- 	aChange isName ifTrue: [
- 		self dictionary at: aChange newName put: (self dictionary at: aChange oldName).
- 		self dictionary removeKey: aChange oldName].
- 	^ aChange
- 	!

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

Item was removed:
- ----- Method: DSChangeCategorizer>>organization (in category 'accessing') -----
- organization
- 	^ categorizer ifNil: [categorizer := self buildCategorizer]!

Item was removed:
- ----- Method: DSChangeCategorizer class>>forClassesAndMethods (in category 'as yet unclassified') -----
- forClassesAndMethods
- 	^ self
- 		default: [:aSymbol | DSGroupedClassChange new]
- 		classify: [:aChange | aChange className]!

Item was removed:
- DSMethodChange subclass: #DSMethodRecord
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'DeltaStreams-Deprecated'!
- 
- !DSMethodRecord commentStamp: 'mtf 9/12/2007 18:16' prior: 0!
- See the comment in DSClassRecord. My instances serve the same purpose, but for methods!

Item was removed:
- ----- Method: DSChangeCategorizer class>>forClasses (in category 'as yet unclassified') -----
- forClasses
- 	^ self
- 		default: [:aSymbol | DSCompositeClassChange new]
- 		classify: [:aChange | aChange className]!

Item was removed:
- DSMarker subclass: #DSSystemEditorMarker
- 	instanceVariableNames: 'editor'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'DeltaStreams-Deprecated'!
- 
- !DSSystemEditorMarker commentStamp: '<historical>' prior: 0!
- My instances add some flags to changes that pass through it, based on the system state maintained in the editor!

Item was removed:
- ----- Method: DSGroupedClassChange>>addChange: (in category 'accessing') -----
- addChange: aChange
- 	aChange isMethodChange ifTrue: [^ self addMethodChange: aChange].
- 	^ super addChange: aChange!

Item was removed:
- ----- Method: DSChangeCategorizer class>>default:classify: (in category 'as yet unclassified') -----
- default: aDefaultBlock classify: aClassifyBlock
- 	^ self new default: aDefaultBlock classify: aClassifyBlock!

Item was removed:
- DSCompositeChange subclass: #DSChangeCategorizer
- 	instanceVariableNames: 'dict defaultBlock classifyBlock categorizer'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'DeltaStreams-Deprecated'!
- 
- !DSChangeCategorizer commentStamp: 'mtf 9/6/2007 23:57' prior: 0!
- My instances automatically group the changes added to them. I implement the Categorizer protocol, so I can be used directly by Browser and friends.!

Item was removed:
- ----- Method: DSSystemEditorMarker>>applyClassCreated: (in category 'class changes') -----
- applyClassCreated: change
- 	"Add a class."
- 
- 	| classEditor superclassEditor |
- 	self ensureSharedPools: change poolDictionaryNames.
- 	superclassEditor := editor at: change superclassName ifAbsent: [editor at: #Object].
- 	classEditor := superclassEditor subclass: change className
- 			instanceVariableNames: change instVarNames asSpaceString
- 			classVariableNames: change classVarNames asSpaceString
- 			poolDictionaries: change poolDictionaryNames asSpaceString
- 			category: change category.
- 	classEditor typeOfClass: change type!

Item was removed:
- ----- Method: DSSystemEditorMarker>>applySharedPoolVarsChanged: (in category 'class changes') -----
- applySharedPoolVarsChanged: change
- 	"Changed shared pool vars. Currently we just raise error if missing!!"
- 
- 	| classEditor |
- 	self ensureSharedPools: change added.
- 	classEditor := self classEditorForChange: change.
- 	change added do: [:each |
- 		classEditor addSharedPool: (classEditor system edResolve: each asSymbol ifAbsent:[
- 			self error: 'Pool variable ',each,' not found!!'])].
- 	change removed do: [:each |
- 		classEditor removeSharedPool: (classEditor system edResolve: each asSymbol ifAbsent:[])].
- 	change moved notEmpty ifTrue: [
- 		classEditor rearrangeSharedPoolVarNames: change movedWithIndices]!

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

Item was removed:
- ----- Method: DSSystemEditorMarker>>applyClassCategoryChanged: (in category 'class changes') -----
- applyClassCategoryChanged: change
- 	"Changed a class category."
- 
- 	(self classEditorForChange: change) category: change newCategory!

Item was removed:
- ----- Method: DSMethodRecord>>applyUsing: (in category 'applying') -----
- applyUsing: anApplier
- 	anApplier applyMethodSnapshot: self!

Item was removed:
- ----- Method: DSClassRecord>>commentChange (in category 'convenience') -----
- commentChange
- 	^ DSClassCommentChange className: className
- 		from: ''
- 		to: comment
- 		oldStamp: ''
- 		newStamp: stamp!

Item was removed:
- ----- Method: DSChangeCategorizer>>reverseDo: (in category 'enumerating') -----
- reverseDo: aBlock
- 	self dictionary do: [:ea | ea reverseDo: aBlock]!

Item was removed:
- ----- Method: DSSystemEditorMarker>>applyInstVarsChanged: (in category 'class changes') -----
- applyInstVarsChanged: change
- 	"Changed instvars."
- 
- 	| classEditor |
- 	classEditor := self classEditorForChange: change.
- 	change added do: [:each | classEditor addInstVarName: each].
- 	change removed do: [:each | classEditor removeInstVarName: each].
- 	change moved notEmpty ifTrue: [
- 		classEditor rearrangeInstVarNames: change movedWithIndices]!



More information about the Packages mailing list