MCPatch.st
author Claus Gittinger <cg@exept.de>
Wed, 22 Nov 2006 14:12:25 +0100
changeset 65 99f7b2e2fe1f
child 155 c7a154a5ff3e
permissions -rw-r--r--
initial checkin

"{ Package: 'stx:goodies/monticello' }"

Object subclass:#MCPatch
	instanceVariableNames:'operations'
	classVariableNames:''
	poolDictionaries:''
	category:'Monticello-Patching'
!


!MCPatch class methodsFor:'as yet unclassified'!

fromBase: baseSnapshot target: targetSnapshot
	^ self new initializeWithBase: baseSnapshot target: targetSnapshot
!

operations: aCollection
	^ self basicNew initializeWithOperations: aCollection
! !

!MCPatch methodsFor:'accessing'!

operations
	^ operations
! !

!MCPatch methodsFor:'applying'!

applyTo: anObject
	operations do: [:ea | ea applyTo: anObject].
! !

!MCPatch methodsFor:'intializing'!

initializeWithBase: baseSnapshot target: targetSnapshot
	| base target |	
	operations _ OrderedCollection new.
	base _ MCDefinitionIndex definitions: baseSnapshot definitions.
	target _ MCDefinitionIndex definitions: targetSnapshot definitions.
	
	target definitions do:
		[:t |
		base
			definitionLike: t
			ifPresent: [:b | (b isSameRevisionAs: t) ifFalse: [operations add: (MCModification of: b to: t)]]
			ifAbsent: [operations add: (MCAddition of: t)]]
		displayingProgress: 'Diffing...'.
		
	base definitions do:
		[:b |
		target
			definitionLike: b
			ifPresent: [:t]
			ifAbsent: [operations add: (MCRemoval of: b)]]		
!

initializeWithOperations: aCollection
	operations _ aCollection
! !

!MCPatch methodsFor:'querying'!

isEmpty
	^ operations isEmpty
! !

!MCPatch methodsFor:'ui'!

browse
	^ (MCPatchBrowser forPatch: self) show
! !

!MCPatch class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCPatch.st,v 1.1 2006-11-22 13:12:25 cg Exp $'
! !