initial checkin
authorClaus Gittinger <cg@exept.de>
Wed, 22 Nov 2006 14:08:25 +0100
changeset 46 11d05551155f
parent 45 8a2cc7383a3a
child 47 6b10e4d5edc1
initial checkin
MCThreeWayMerger.st
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/MCThreeWayMerger.st	Wed Nov 22 14:08:25 2006 +0100
@@ -0,0 +1,144 @@
+"{ Package: 'stx:goodies/monticello' }"
+
+MCMerger subclass:#MCThreeWayMerger
+	instanceVariableNames:'index operations provisions redundantAdds'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Monticello-Merging'
+!
+
+
+!MCThreeWayMerger class methodsFor:'as yet unclassified'!
+
+base: aSnapshot patch: aPatch
+	aPatch isEmpty ifTrue: [MCNoChangesException signal].
+	^ self new
+		addBaseSnapshot: aSnapshot;
+		applyPatch: aPatch;
+		yourself
+		
+!
+
+base: aSnapshot target: targetSnapshot ancestor: ancestorSnapshot
+	^ self base: aSnapshot patch: (targetSnapshot patchRelativeToBase: ancestorSnapshot)
+!
+
+new
+	^ self basicNew initialize
+! !
+
+!MCThreeWayMerger methodsFor:'as yet unclassified'!
+
+addBaseSnapshot: aSnapshot
+	aSnapshot definitions do:
+		[:ea |
+		index add: ea.
+		provisions addAll: ea provisions]
+!
+
+addDefinition: aDefinition
+	index
+		definitionLike: aDefinition
+		ifPresent: [:other |
+			(self removalForDefinition: aDefinition)
+				ifNotNilDo:
+					[:op |
+					self addOperation: (MCModification of: other to: aDefinition).
+					self removeOperation: op.
+					^ self].
+			other = aDefinition
+				ifFalse: [self addConflictWithOperation: (MCModification of: other to: aDefinition)]
+				ifTrue: [self redundantAdds add: aDefinition]]
+		ifAbsent: [self addOperation: (MCAddition of: aDefinition)]
+!
+
+addOperation: anOperation
+	self operations add: anOperation
+!
+
+applyPatch: aPatch
+	aPatch applyTo: self
+!
+
+applyTo: anObject
+	super applyTo: anObject.
+	self operations do: [:ea | ea applyTo: anObject]
+!
+
+baseSnapshot
+	^ (MCSnapshot fromDefinitions: index definitions)
+!
+
+initialize
+	index _ MCDefinitionIndex new.
+	provisions _ Set new
+!
+
+modificationConflictForDefinition: aDefinition
+	^ conflicts ifNotNil:
+		[conflicts detect:
+			[:ea | (ea definition isRevisionOf: aDefinition) and:
+				[ea operation isModification]] ifNone: []]
+!
+
+modifyDefinition: baseDefinition to: targetDefinition
+	index
+		definitionLike: baseDefinition
+		ifPresent: [:other | other = baseDefinition
+								ifTrue: [self addOperation: (MCModification of:  baseDefinition to: targetDefinition)]
+								ifFalse: [other = targetDefinition
+											ifFalse: [self addConflictWithOperation:
+														(MCModification of: other to: targetDefinition)]]]
+		ifAbsent: [self addConflictWithOperation: (MCAddition of: targetDefinition)]
+!
+
+operations
+	^ operations ifNil: [operations _ OrderedCollection new]
+!
+
+provisions
+	^ provisions
+!
+
+redundantAdds
+	^ redundantAdds ifNil: [redundantAdds _ Set new]
+!
+
+removalForDefinition: aDefinition
+	^ operations ifNotNil:
+		[operations
+			detect: [:ea | (ea definition isRevisionOf: aDefinition) and: [ea isRemoval]]
+			ifNone: []]
+!
+
+removeConflict: aConflict
+	conflicts remove: aConflict
+!
+
+removeDefinition: aDefinition
+	index
+		definitionLike: aDefinition
+		ifPresent: [:other | other = aDefinition
+								ifTrue:
+									[(self modificationConflictForDefinition: aDefinition)
+										ifNotNilDo:
+											[:c |
+											self addOperation: c operation.
+											self removeConflict: c.
+											^ self]. 
+									(self redundantAdds includes: aDefinition)
+										ifFalse: [self addOperation: (MCRemoval of: aDefinition)]]
+								ifFalse:
+									[self addConflictWithOperation: (MCRemoval of: other)]]
+		ifAbsent: []
+!
+
+removeOperation: anOperation
+	operations remove: anOperation
+! !
+
+!MCThreeWayMerger class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCThreeWayMerger.st,v 1.1 2006-11-22 13:08:25 cg Exp $'
+! !