Removed test classes from stx:goodies/monticello - they're in tests sub package. jv
authorJan Vrany <jan.vrany@fit.cvut.cz>
Sun, 10 May 2015 05:53:16 +0100
branchjv
changeset 995 92bb466548a9
parent 994 73e11bcc0ff1
child 996 ab948c69360b
Removed test classes from stx:goodies/monticello - they're in tests sub package.
MCAncestryTest.st
MCCannotLoadMethodError.st
MCChangeNotificationTest.st
MCChangeSelector.st
MCClassDefinitionTest.st
MCDependencySorterTest.st
MCDependentsWrapper.st
MCDictionaryRepositoryTest.st
MCDirectoryRepositoryTest.st
MCFileInTest.st
MCFileRepositoryInspector.st
MCInitializationTest.st
MCMczInstallerTest.st
MCMergeBrowser.st
MCMergingTest.st
MCMethodDefinitionTest.st
MCMockASubclass.st
MCMockClassA.st
MCMockClassB.st
MCMockClassD.st
MCMockClassE.st
MCMockClassF.st
MCMockClassG.st
MCMockClassH.st
MCMockClassI.st
MCOrganizationTest.st
MCPackageTest.st
MCPatchTest.st
MCRepositoryInspector.st
MCRepositoryTest.st
MCSMCacheRepository.st
MCSaveVersionDialog.st
MCScannerTest.st
MCSerializationTest.st
MCSnapshotBrowser.st
MCSnapshotBrowserTest.st
MCSnapshotResource.st
MCSnapshotTest.st
MCStReaderTest.st
MCStWriterTest.st
MCTestCase.st
MCToolWindowBuilder.st
MCVersionTest.st
MCWorkingCopyBrowser.st
MCWorkingCopyTest.st
MCWorkingHistoryBrowser.st
Make.proto
bc.mak
extensions.st
stx_goodies_monticello.st
--- a/MCAncestryTest.st	Thu Apr 30 21:53:12 2015 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,146 +0,0 @@
-"{ Package: 'stx:goodies/monticello' }"
-
-MCTestCase subclass:#MCAncestryTest
-	instanceVariableNames:''
-	classVariableNames:''
-	poolDictionaries:''
-	category:'Monticello-Tests'
-!
-
-
-!MCAncestryTest methodsFor:'asserting'!
-
-assertCommonAncestorOf: leftName and: rightName in: options in: tree
-	| left right ancestor |
-	left := self versionForName: leftName in: tree.
-	right := self versionForName: rightName in: tree.
-	
-	ancestor := left commonAncestorWith: right.
-	
-	self assert: (options includes: ancestor name)
-!
-
-assertCommonAncestorOf: leftName and: rightName is: ancestorName in: tree
-	self assertCommonAncestorOf: leftName and: rightName in: (Array with: ancestorName) in: tree
-!
-
-assertNamesOf: versionInfoCollection are: nameArray
-	| names |
-	names := versionInfoCollection collect: [:ea | ea name].
-	
-	self assert: names asArray = nameArray
-!
-
-assertPathTo: aSymbol is: anArray
-	self
-		assertNamesOf: (self tree allAncestorsOnPathTo: (self treeFrom: {aSymbol}))
-		are: anArray
-! !
-
-!MCAncestryTest methodsFor:'building'!
-
-tree
-	^ self treeFrom:
-		#(c1
-			((e2
-				((e1
-					((a1
-						(('00')))))))
-			(a2
-				((a1
-					(('00')))))
-			(b3
-				((b2
-					((b1
-						((b0
-							(('00')))))))
-				(a1
-					(('00')))))
-			(d1)))
-!
-
-twoPersonTree
-	^ self treeFrom:
-		#(c1
-			((a4
-				((a1)
-				(b3
-					((b2
-						((a1)))))))
-			(b5
-				((b2
-					((a1)))))))
-!
-
-versionForName: name in: tree
-        (tree name = name) ifTrue: [^ tree].
-        
-        tree ancestors do: [:ea | (self versionForName: name in: ea) ifNotNil: 
-                [^ (self versionForName: name in: ea)]].
-        ^ nil
-
-    "Modified: / 26-08-2009 / 13:35:20 / Jaroslav Havlin <havlij6@fel.cvut.cz>"
-! !
-
-!MCAncestryTest methodsFor:'tests'!
-
-testCommonAncestors
-	self assertCommonAncestorOf: #a2 and: #e2 is: #a1 in: self tree.
-	self assertCommonAncestorOf: #e2 and: #b3 is: #a1 in: self tree.
-	self assertCommonAncestorOf: #b2 and: #e2 is: #'00' in: self tree.
-	
-	self assertCommonAncestorOf: #a4 and: #b5 in: #(b2 a1) in: self twoPersonTree.
-	self assertCommonAncestorOf: #b5 and: #b3 is: #b2 in: self twoPersonTree.
-	self assertCommonAncestorOf: #b2 and: #a4 is: #b2 in: self twoPersonTree.
-	self assertCommonAncestorOf: #b2 and: #b2 is: #b2 in: self twoPersonTree.
-	self assertCommonAncestorOf: #b2 and: #a1 is: #a1 in: self twoPersonTree.
-	self assertCommonAncestorOf: #a1 and: #b2 is: #a1 in: self twoPersonTree.
-!
-
-testDescendants
-	| c1 a1 b3 q1 q2 c2 |
-	c1 := self tree.
-	a1 := self treeFrom: #(a1 (('00'))).
-	b3 := self treeFrom: #(b3
-				((b2
-					((b1
-						((b0
-							(('00')))))))
-				(a1
-					(('00'))))).
-	q1 := MCWorkingAncestry new addAncestor: a1.
-	q2 := MCWorkingAncestry new addAncestor: q1.
-	self assert: (q2 commonAncestorWith: b3) = a1.
-	self assert: (b3 commonAncestorWith: q2) = a1.
-	self assert: (q2 commonAncestorWith: c1) = a1.
-	self assert: (c1 commonAncestorWith: q2) = a1.
-	q1 addStepChild: c1.
-	self assert: (q2 commonAncestorWith: c1) = q1.
-	self assert: (c1 commonAncestorWith: q2) = q1.
-	c2 := MCWorkingAncestry new addAncestor: c1.
-	self assert: (q2 commonAncestorWith: c2) = q1.
-	self assert: (c2 commonAncestorWith: q2) = q1.
-
-!
-
-testLinearPath
-	self assertPathTo: #b1 is: #(b3 b2)
-!
-
-testPathToMissingAncestor
-	self assert: (self tree allAncestorsOnPathTo: MCVersionInfo new) isEmpty
-! !
-
-!MCAncestryTest class methodsFor:'documentation'!
-
-version
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCAncestryTest.st,v 1.2 2011-08-20 12:04:04 cg Exp $'
-!
-
-version_CVS
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCAncestryTest.st,v 1.2 2011-08-20 12:04:04 cg Exp $'
-!
-
-version_SVN
-    ^ '§Id: MCAncestryTest.st 5 2010-08-29 07:30:29Z vranyj1 §'
-! !
--- a/MCCannotLoadMethodError.st	Thu Apr 30 21:53:12 2015 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,33 +0,0 @@
-"{ Package: 'stx:goodies/monticello' }"
-
-ProceedableError subclass:#MCCannotLoadMethodError
-	instanceVariableNames:''
-	classVariableNames:''
-	poolDictionaries:''
-	category:'SCM-Monticello-St/X UI'
-!
-
-
-!MCCannotLoadMethodError methodsFor:'accessing'!
-
-methodDefinition
-    ^ parameter
-
-    "Created: / 11-09-2012 / 09:51:17 / cg"
-!
-
-methodDefinition:anMCMethodDefinition
-    parameter := anMCMethodDefinition
-
-    "Created: / 11-09-2012 / 09:51:35 / cg"
-! !
-
-!MCCannotLoadMethodError class methodsFor:'documentation'!
-
-version
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCCannotLoadMethodError.st,v 1.1 2012-09-11 21:01:06 cg Exp $'
-!
-
-version_CVS
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCCannotLoadMethodError.st,v 1.1 2012-09-11 21:01:06 cg Exp $'
-! !
--- a/MCChangeNotificationTest.st	Thu Apr 30 21:53:12 2015 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,80 +0,0 @@
-"{ Package: 'stx:goodies/monticello' }"
-
-MCTestCase subclass:#MCChangeNotificationTest
-	instanceVariableNames:'workingCopy'
-	classVariableNames:''
-	poolDictionaries:''
-	category:'Monticello-Tests'
-!
-
-
-!MCChangeNotificationTest methodsFor:'events'!
-
-modifiedEventFor: aSelector ofClass: aClass
-	| method |
-	method := aClass compiledMethodAt: aSelector.
-	^ ModifiedEvent 
-				methodChangedFrom: method
-				to: method
-				selector: aSelector
-				inClass: aClass.
-
-! !
-
-!MCChangeNotificationTest methodsFor:'private'!
-
-foreignMethod
-	"see testForeignMethodModified"
-! !
-
-!MCChangeNotificationTest methodsFor:'running'!
-
-setUp
-	workingCopy := MCWorkingCopy forPackage: self mockPackage.
-	
-!
-
-tearDown
-	workingCopy unregister
-! !
-
-!MCChangeNotificationTest methodsFor:'tests'!
-
-testCoreMethodModified
-	| event |
-	workingCopy modified: false.
-	event := self modifiedEventFor: #one ofClass: self mockClassA.
-	MCWorkingCopy methodModified: event.
-	self assert: workingCopy modified
-!
-
-testExtMethodModified
-	| event mref |
-	workingCopy modified: false.
-	mref := workingCopy packageInfo extensionMethods first.
-	event := self modifiedEventFor: mref methodSymbol ofClass: mref actualClass.
-	MCWorkingCopy methodModified: event.
-	self assert: workingCopy modified
-!
-
-testForeignMethodModified
-	| event |
-	workingCopy modified: false.
-	event := self modifiedEventFor: #foreignMethod ofClass: self class.
-	MCWorkingCopy methodModified: event.
-	self deny: workingCopy modified
-! !
-
-!MCChangeNotificationTest class methodsFor:'documentation'!
-
-version
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCChangeNotificationTest.st,v 1.1 2011-08-20 12:25:29 cg Exp $'
-!
-
-version_CVS
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCChangeNotificationTest.st,v 1.1 2011-08-20 12:25:29 cg Exp $'
-!
-
-version_SVN
-    ^ '§Id: MCChangeNotificationTest.st 5 2010-08-29 07:30:29Z vranyj1 §'
-! !
--- a/MCChangeSelector.st	Thu Apr 30 21:53:12 2015 +0200
+++ b/MCChangeSelector.st	Sun May 10 05:53:16 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/monticello' }"
 
+"{ NameSpace: Smalltalk }"
+
 MCPatchBrowser subclass:#MCChangeSelector
 	instanceVariableNames:'kept'
 	classVariableNames:''
@@ -82,3 +84,4 @@
 version
     ^ '$Header: /cvs/stx/stx/goodies/monticello/MCChangeSelector.st,v 1.2 2012-09-11 21:01:15 cg Exp $'
 ! !
+
--- a/MCClassDefinitionTest.st	Thu Apr 30 21:53:12 2015 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,169 +0,0 @@
-"{ Package: 'stx:goodies/monticello' }"
-
-MCTestCase subclass:#MCClassDefinitionTest
-	instanceVariableNames:'previousChangeSet'
-	classVariableNames:''
-	poolDictionaries:''
-	category:'Monticello-Tests'
-!
-
-
-!MCClassDefinitionTest class methodsFor:'as yet unclassified'!
-
-classAComment
-	^ 'This is a mock class. The Monticello tests manipulated it to simulate a developer modifying code in the image.'
-!
-
-classACommentStamp
-	^  'cwp 8/10/2003 16:43'
-!
-
-restoreClassAComment
-	Smalltalk 
-		at: #MCMockClassA 
-		ifPresent: [:a | a classComment: self classAComment stamp: self classACommentStamp]
-! !
-
-!MCClassDefinitionTest methodsFor:'as yet unclassified'!
-
-classAComment
-	^ self class classAComment
-!
-
-creationMessage
-	^ MessageSend
-		receiver: MCClassDefinition
-		selector: #name:superclassName:category:instVarNames:classVarNames:poolDictionaryNames:classInstVarNames:type:comment:commentStamp:
-!
-
-tearDown
-        Smalltalk at: #'MCMockClassC' ifPresent: [:c | c removeFromSystem]
-
-    "Modified: / 09-09-2010 / 15:23:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-testCannotLoad
-	| d |
-	d :=  self mockClass: 'MCMockClassC' super: 'NotAnObject'.
-	self should: [d load] raise: Error.
-	self deny: (Smalltalk hasClassNamed: 'MCMockClassC').
-!
-
-testComparison
-	| d1 d2 d3 d4 |
-	d1 := self mockClass: 'A' super: 'X'.
-	d2 := self mockClass: 'A' super: 'Y'.
-	d3 := self mockClass: 'B' super: 'X'.
-	d4 := self mockClass: 'B' super: 'X'.
-	
-	self assert: (d1 isRevisionOf: d2).
-	self deny: (d1 isSameRevisionAs: d2).
-
-	self assert: (d3 isRevisionOf: d4).
-	self assert: (d3 isSameRevisionAs: d4).
-	
-	self deny: (d1 isRevisionOf: d3).
-	self deny: (d4 isRevisionOf: d2).
-!
-
-testCreation
-        | d |
-        d :=  self mockClassA asClassDefinition.
-        self assert: d className = #MCMockClassA.
-        self assert: d superclassName = #MCMock.
-        self assert: d type = #normal.
-        self assert: d category = self mockCategoryName.
-        self assert: d instVarNames asArray = #('ivar').
-        self assert: d classVarNames asArray = #('CVar').
-        self assert: d classInstVarNames asArray = #().
-        self assert: d comment isString.
-        self assert: d comment = self classAComment.
-        "/TODO: Fix it later
-        "/self assert: d commentStamp = self mockClassA organization commentStamp
-
-    "Modified: / 11-09-2010 / 18:24:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-testDefinitionString
-        | d |
-        d := self mockClassA asClassDefinition.
-        self assert: d definitionString = self mockClassA mcDefinition.
-
-    "Modified: / 11-09-2010 / 18:04:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-testEquals
-	| a b |
-	a := self mockClass: 'ClassA' super: 'SuperA'.
-	b := self mockClass: 'ClassA' super: 'SuperA'.
-	self assert: a = b
-!
-
-testEqualsSensitivity
-	| message a b defA args defB |
-	message := self creationMessage.
-	a := #(ClassA SuperA CategoryA #(iVarA) #(CVarA) #(PoolA) #(ciVarA)
-			typeA 'A comment' 'A').
-	b := #(ClassB SuperB CategoryB #(iVarB) #(CVarB) #(PoolB) #(ciVarB)
-			typeB 'B comment' 'B').
-	
-	defA := message valueWithArguments: a.
-	1 to: 8 do: [:index |
-				args := a copy.
-				args at: index put: (b at: index).
-				defB := message valueWithArguments: args.
-				self deny: defA = defB.]
-!
-
-testKindOfSubclass
-        | classes d |
-        classes := Array 
-                    with: self mockClassA
-                    with: String 
-                    with: Context
-                    with: WeakArray
-                    with: Float.
-        classes do: [:c |
-                d :=  c asClassDefinition.
-                self assert: d kindOfSubclass = c kindOfSubclass.
-        ].
-
-    "Modified: / 28-08-2010 / 23:03:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-testLoadAndUnload
-
-
-        | d c |
-        d :=  self mockClass: 'MCMockClassC' super: 'Object'.
-        d load.
-        self assert: (Smalltalk hasClassNamed: 'MCMockClassC').
-        c := (Smalltalk classNamed: 'MCMockClassC').
-        self assert: (c isKindOf: Class).
-        self assert: c superclass = Object.
-        self assert: c instVarNames isEmpty.
-        self assert: c classVarNames isEmpty.
-        self assert: c sharedPools isEmpty.
-        self assert: c category = self mockCategoryName.
-        self assert: c organization classComment = (self commentForClass: 'MCMockClassC').
-        "/Fix it later
-        "/self assert: c organization commentStamp = (self commentStampForClass: 'MCMockClassC').
-        d unload.
-        self deny: (Smalltalk hasClassNamed: 'MCMockClassC').
-
-    "Modified: / 11-09-2010 / 17:54:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-! !
-
-!MCClassDefinitionTest class methodsFor:'documentation'!
-
-version
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCClassDefinitionTest.st,v 1.1 2011-08-20 12:03:37 cg Exp $'
-!
-
-version_CVS
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCClassDefinitionTest.st,v 1.1 2011-08-20 12:03:37 cg Exp $'
-!
-
-version_SVN
-    ^ '§Id: MCClassDefinitionTest.st 7 2010-09-12 07:18:55Z vranyj1 §'
-! !
--- a/MCDependencySorterTest.st	Thu Apr 30 21:53:12 2015 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,121 +0,0 @@
-"{ Package: 'stx:goodies/monticello' }"
-
-TestCase subclass:#MCDependencySorterTest
-	instanceVariableNames:''
-	classVariableNames:''
-	poolDictionaries:''
-	category:'Monticello-Tests'
-!
-
-
-!MCDependencySorterTest methodsFor:'asserting'!
-
-assertItems: anArray orderAs: depOrder withRequired: missingDeps toLoad: unloadableItems
-	self assertItems: anArray orderAs: depOrder withRequired: missingDeps  toLoad: unloadableItems  extraProvisions: #()
-!
-
-assertItems: anArray orderAs: depOrder withRequired: missingDeps toLoad: unloadableItems extraProvisions: provisions
-	| order sorter items missing unloadable |
-	items := anArray collect: [:ea | self itemWithSpec: ea].
-	sorter := MCDependencySorter items: items.
-	sorter addExternalProvisions: provisions.
-	order := (sorter orderedItems collect: [:ea | ea name]) asArray.
-	self assert: order = depOrder.
-	missing := sorter externalRequirements.
-	self assert: missing asSet = missingDeps asSet.
-	unloadable := (sorter itemsWithMissingRequirements collect: [:ea | ea name]) asArray.
-	self assert: unloadable asSet = unloadableItems asSet
-! !
-
-!MCDependencySorterTest methodsFor:'building'!
-
-itemWithSpec: anArray
-	^ MCMockDependentItem new
-		name: anArray first;
-		provides: anArray second;
-		requires: anArray third
-! !
-
-!MCDependencySorterTest methodsFor:'tests'!
-
-testCascadingUnresolved
-	self assertItems: #(
-		(a (x) (z))
-		(b () (x))
-		(c () ()))
-	orderAs: #(c)
-	withRequired: #(z)
-	toLoad: #(a b)	
-!
-
-testCycle
-	self assertItems: #(
-		(a (x) (y))
-		(b (y) (x)))
-	orderAs: #()
-	withRequired: #()
-	toLoad: #(a b)	
-!
-
-testExtraProvisions
-	self assertItems:
-		#((a (x) (z))
-		(b () (x)))
-	orderAs: #(a b)
-	withRequired: #()
-	toLoad: #()	
-	extraProvisions: #(x z)
-!
-
-testMultiRequirementOrdering
-	self assertItems: #(
-		(a (x) (z))
-		(b (y) ())
-		(c (z) ())
-		(d () (x y z)))
-		orderAs: #(b c a d)
-		withRequired: #()
-		toLoad: #()
-!
-
-testSimpleOrdering
-	self assertItems: #((a (x) ())
-								 (c () (y))
-								 (b (y) (x)))
-		orderAs: #(a b c)
-		withRequired: #()
-		toLoad: #()
-!
-
-testSimpleUnresolved
-	self assertItems: #(
-		(a () (z)))
-	orderAs: #()
-	withRequired: #(z)
-	toLoad: #(a)
-		
-!
-
-testUnusedAlternateProvider
-	self assertItems: #(
-		(a (x) (z))
-		(b () (x))
-		(c (x) ()))
-	orderAs: #(c b)
-	withRequired: #(z)
-	toLoad: #(a)	
-! !
-
-!MCDependencySorterTest class methodsFor:'documentation'!
-
-version
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCDependencySorterTest.st,v 1.1 2011-08-20 12:20:16 cg Exp $'
-!
-
-version_CVS
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCDependencySorterTest.st,v 1.1 2011-08-20 12:20:16 cg Exp $'
-!
-
-version_SVN
-    ^ '§Id: MCDependencySorterTest.st 5 2010-08-29 07:30:29Z vranyj1 §'
-! !
--- a/MCDependentsWrapper.st	Thu Apr 30 21:53:12 2015 +0200
+++ b/MCDependentsWrapper.st	Sun May 10 05:53:16 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/monticello' }"
 
+"{ NameSpace: Smalltalk }"
+
 ListItemWrapper subclass:#MCDependentsWrapper
 	instanceVariableNames:''
 	classVariableNames:''
@@ -37,3 +39,4 @@
 version
     ^ '$Header: /cvs/stx/stx/goodies/monticello/MCDependentsWrapper.st,v 1.2 2012-09-11 21:21:24 cg Exp $'
 ! !
+
--- a/MCDictionaryRepositoryTest.st	Thu Apr 30 21:53:12 2015 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,41 +0,0 @@
-"{ Package: 'stx:goodies/monticello' }"
-
-MCRepositoryTest subclass:#MCDictionaryRepositoryTest
-	instanceVariableNames:'dict'
-	classVariableNames:''
-	poolDictionaries:''
-	category:'Monticello-Tests'
-!
-
-
-!MCDictionaryRepositoryTest methodsFor:'as yet unclassified'!
-
-addVersion: aVersion
-	dict at: aVersion info put: aVersion
-!
-
-deleteNode: aNode
-	dict removeKey: aNode
-!
-
-dictionary
-	^ dict ifNil: [dict := Dictionary new]
-!
-
-setUp
-	repository :=  MCDictionaryRepository new dictionary: self dictionary
-! !
-
-!MCDictionaryRepositoryTest class methodsFor:'documentation'!
-
-version
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCDictionaryRepositoryTest.st,v 1.1 2011-08-20 12:33:24 cg Exp $'
-!
-
-version_CVS
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCDictionaryRepositoryTest.st,v 1.1 2011-08-20 12:33:24 cg Exp $'
-!
-
-version_SVN
-    ^ '§Id: MCDictionaryRepositoryTest.st 5 2010-08-29 07:30:29Z vranyj1 §'
-! !
--- a/MCDirectoryRepositoryTest.st	Thu Apr 30 21:53:12 2015 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,47 +0,0 @@
-"{ Package: 'stx:goodies/monticello' }"
-
-MCRepositoryTest subclass:#MCDirectoryRepositoryTest
-	instanceVariableNames:'directory'
-	classVariableNames:''
-	poolDictionaries:''
-	category:'Monticello-Tests'
-!
-
-
-!MCDirectoryRepositoryTest methodsFor:'as yet unclassified'!
-
-addVersion: aVersion
-	| file |
-	file := FileStream newFileNamed: (directory fullNameFor: aVersion fileName).
-	aVersion fileOutOn: file.
-	file close.
-!
-
-directory
-	directory ifNil:
-		[directory := FileDirectory default directoryNamed: 'mctest'.
-		directory assureExistence].
-	^ directory
-!
-
-setUp
-	repository := MCDirectoryRepository new directory: self directory
-!
-
-tearDown
-	self directory recursiveDelete
-! !
-
-!MCDirectoryRepositoryTest class methodsFor:'documentation'!
-
-version
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCDirectoryRepositoryTest.st,v 1.1 2011-08-20 12:19:09 cg Exp $'
-!
-
-version_CVS
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCDirectoryRepositoryTest.st,v 1.1 2011-08-20 12:19:09 cg Exp $'
-!
-
-version_SVN
-    ^ '§Id: MCDirectoryRepositoryTest.st 5 2010-08-29 07:30:29Z vranyj1 §'
-! !
--- a/MCFileInTest.st	Thu Apr 30 21:53:12 2015 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,81 +0,0 @@
-"{ Package: 'stx:goodies/monticello' }"
-
-MCTestCase subclass:#MCFileInTest
-	instanceVariableNames:'stream expected diff'
-	classVariableNames:''
-	poolDictionaries:''
-	category:'Monticello-Tests'
-!
-
-
-!MCFileInTest methodsFor:'asserting'!
-
-assertNoChange
-	| actual |
-	actual := MCSnapshotResource takeSnapshot.
-	diff := actual patchRelativeToBase: expected.
-	self assert: diff isEmpty
-! !
-
-!MCFileInTest methodsFor:'running'!
-
-setUp
-        expected := self mockSnapshot.
-        stream := RWBinaryOrTextStream on: String new.
-
-    "Modified: / 12-09-2010 / 15:29:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-tearDown
-	(diff isNil or: [diff isEmpty not])
-		 ifTrue: [expected updatePackage: self mockPackage]
-! !
-
-!MCFileInTest methodsFor:'testing'!
-
-alterInitialState
-	self mockClassA touchCVar
-!
-
-assertFileOutFrom: writerClass canBeFiledInWith: aBlock
-	(writerClass on: stream) writeSnapshot: self mockSnapshot.
-	self alterInitialState.
-	self assertSuccessfulLoadWith: aBlock.
-	self mockPackage unload.
-	self assertSuccessfulLoadWith: aBlock.
-
-!
-
-assertInitializersCalled
-	| cvar |
-	cvar := self mockClassA cVar.
-	self assert: cvar = #initialized
-!
-
-assertSuccessfulLoadWith: aBlock
-	stream reset.
-	aBlock value.
-	self assertNoChange.
-	self assertInitializersCalled.
-!
-
-testStWriter
-	self
-		assertFileOutFrom: MCStWriter
-		canBeFiledInWith: [stream fileIn].
-
-! !
-
-!MCFileInTest class methodsFor:'documentation'!
-
-version
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCFileInTest.st,v 1.1 2011-08-20 12:32:22 cg Exp $'
-!
-
-version_CVS
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCFileInTest.st,v 1.1 2011-08-20 12:32:22 cg Exp $'
-!
-
-version_SVN
-    ^ '§Id: MCFileInTest.st 8 2010-09-12 17:15:52Z vranyj1 §'
-! !
--- a/MCFileRepositoryInspector.st	Thu Apr 30 21:53:12 2015 +0200
+++ b/MCFileRepositoryInspector.st	Sun May 10 05:53:16 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/monticello' }"
 
+"{ NameSpace: Smalltalk }"
+
 MCVersionInspector subclass:#MCFileRepositoryInspector
 	instanceVariableNames:'repository versions loaded newer inherited selectedPackage
 		selectedVersion order versionInfo'
--- a/MCInitializationTest.st	Thu Apr 30 21:53:12 2015 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,45 +0,0 @@
-"{ Package: 'stx:goodies/monticello' }"
-
-MCTestCase subclass:#MCInitializationTest
-	instanceVariableNames:''
-	classVariableNames:''
-	poolDictionaries:''
-	category:'Monticello-Tests'
-!
-
-
-!MCInitializationTest class methodsFor:'as yet unclassified'!
-
-isAbstract
-        ^ (Smalltalk classNamed: #MczInstaller) notNil
-
-    "Modified: / 18-08-2009 / 10:04:07 / Jan Vrany <vranyj1@fel.cvut.cz>"
-! !
-
-!MCInitializationTest methodsFor:'as yet unclassified'!
-
-tearDown
-	(MCWorkingCopy forPackage: self mockPackage) unregister
-!
-
-testWorkingCopy
-	MczInstaller storeVersionInfo: self mockVersion.
-	MCWorkingCopy initialize.
-	MCWorkingCopy allManagers
-						detect: [:man | man package name = self mockPackage name]
-						ifNone: [self assert: false]
-! !
-
-!MCInitializationTest class methodsFor:'documentation'!
-
-version
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCInitializationTest.st,v 1.1 2011-08-20 12:07:45 cg Exp $'
-!
-
-version_CVS
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCInitializationTest.st,v 1.1 2011-08-20 12:07:45 cg Exp $'
-!
-
-version_SVN
-    ^ '§Id: MCInitializationTest.st 5 2010-08-29 07:30:29Z vranyj1 §'
-! !
--- a/MCMczInstallerTest.st	Thu Apr 30 21:53:12 2015 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,103 +0,0 @@
-"{ Package: 'stx:goodies/monticello' }"
-
-MCTestCase subclass:#MCMczInstallerTest
-	instanceVariableNames:'expected diff'
-	classVariableNames:''
-	poolDictionaries:''
-	category:'Monticello-Tests'
-!
-
-
-!MCMczInstallerTest class methodsFor:'as yet unclassified'!
-
-isAbstract
-        ^ (Smalltalk classNamed: #MczInstaller) notNil
-
-    "Modified: / 18-08-2009 / 10:04:50 / Jan Vrany <vranyj1@fel.cvut.cz>"
-!
-
-suite
-        ^ (Smalltalk classNamed: #MczInstaller) notNil
-                ifTrue: [super suite]
-                ifFalse: [TestSuite new name: self name asString]
-
-    "Modified: / 18-08-2009 / 10:30:22 / Jan Vrany <vranyj1@fel.cvut.cz>"
-! !
-
-!MCMczInstallerTest methodsFor:'as yet unclassified'!
-
-assertDict: dict matchesInfo: info
-	#(name id message date time author)
-		do: [:sel |  (info perform: sel) ifNotNil: [:i | dict at: sel ifPresent: [:d | self assert: i = d]]].
-	info ancestors 
-			with: (dict at: #ancestors) 
-			do: [:i :d | self assertDict: d matchesInfo: i]
-!
-
-assertNoChange
-	| actual |
-	actual := MCSnapshotResource takeSnapshot.
-	diff := actual patchRelativeToBase: expected snapshot.
-	self assert: diff isEmpty
-!
-
-assertVersionInfoPresent
-	| dict info |
-	dict := MczInstaller versionInfo at: self mockPackage name.
-	info := expected info.
-	self assertDict: dict matchesInfo: info.
-!
-
-deleteFile
-	(FileDirectory default fileExists: self fileName)
-		ifTrue: [FileDirectory default deleteFileNamed: self fileName]
-!
-
-fileName
-	^ 'InstallerTest.mcz'
-!
-
-fileStream
-	^ FileStream forceNewFileNamed: self fileName.
-!
-
-setUp
-	expected := self mockVersion.
-	self change: #one toReturn: 2.
-!
-
-tearDown
-	expected snapshot updatePackage: self mockPackage.
-	self deleteFile.
-!
-
-testInstallFromFile
-	MCMczWriter fileOut: expected on: self fileStream.
-	MczInstaller installFileNamed: self fileName.
-	self assertNoChange.
-!
-
-testInstallFromStream
-        | stream |
-        stream := ReadWriteStream on: String new.
-        MCMczWriter fileOut: expected on: stream.
-        MczInstaller installStream: stream reset.
-        self assertNoChange.
-        self assertVersionInfoPresent.
-
-    "Modified: / 29-08-2010 / 08:50:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-! !
-
-!MCMczInstallerTest class methodsFor:'documentation'!
-
-version
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCMczInstallerTest.st,v 1.1 2011-08-20 12:29:34 cg Exp $'
-!
-
-version_CVS
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCMczInstallerTest.st,v 1.1 2011-08-20 12:29:34 cg Exp $'
-!
-
-version_SVN
-    ^ '§Id: MCMczInstallerTest.st 5 2010-08-29 07:30:29Z vranyj1 §'
-! !
--- a/MCMergeBrowser.st	Thu Apr 30 21:53:12 2015 +0200
+++ b/MCMergeBrowser.st	Sun May 10 05:53:16 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/monticello' }"
 
+"{ NameSpace: Smalltalk }"
+
 MCPatchBrowser subclass:#MCMergeBrowser
 	instanceVariableNames:'conflicts merger ok'
 	classVariableNames:''
@@ -153,3 +155,4 @@
 version
     ^ '$Header: /cvs/stx/stx/goodies/monticello/MCMergeBrowser.st,v 1.2 2012-09-11 21:12:50 cg Exp $'
 ! !
+
--- a/MCMergingTest.st	Thu Apr 30 21:53:12 2015 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,202 +0,0 @@
-"{ Package: 'stx:goodies/monticello' }"
-
-MCTestCase subclass:#MCMergingTest
-	instanceVariableNames:'conflictBlock conflicts'
-	classVariableNames:''
-	poolDictionaries:''
-	category:'Monticello-Tests'
-!
-
-
-!MCMergingTest methodsFor:'asserting'!
-
-assert: aCollection hasElements: anArray
-	self assert: (aCollection collect: [:ea | ea token]) asSet = anArray asSet
-!
-
-assertMerge: local with: remote base: ancestor gives: result conflicts: conflictResult
-	| merger |
-	conflicts := #().
-	merger := MCThreeWayMerger
-				base: (self snapshotWithElements: local)
-				target: (self snapshotWithElements: remote)
-				ancestor: (self snapshotWithElements: ancestor).
-	merger conflicts do: [:ea | self handleConflict: ea].
-	self assert: merger mergedSnapshot definitions hasElements: result.
-	self assert: conflicts asSet = conflictResult asSet.
-! !
-
-!MCMergingTest methodsFor:'emulating'!
-
-handleConflict: aConflict       
-        | d l r|
-        l := #removed.
-        r := #removed.
-        (d := aConflict localDefinition) ifNotNil: [ l := d token].
-        (d := aConflict remoteDefinition) ifNotNil: [ r := d token].       
-        conflicts := conflicts copyWith: (Array with: r with: l).
-        (l = #removed or: [r = #removed])
-                ifTrue: [aConflict chooseRemote]
-                ifFalse:
-                        [l > r
-                                ifTrue: [aConflict chooseLocal]
-                                ifFalse: [aConflict chooseRemote]]
-
-    "Modified: / 12-09-2010 / 17:38:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-snapshotWithElements: anArray
-	^ MCSnapshot
-		fromDefinitions: (anArray collect: [:t | self mockToken: t])
-! !
-
-!MCMergingTest methodsFor:'tests'!
-
-testAdditiveConflictlessMerge
-	self
-		assertMerge: #(a1 b1)
-				with: #(a1 c1)
-				base: #(a1)
-			
-				gives: #(a1 b1 c1)
-				conflicts: #()
-!
-
-testComplexConflictlessMerge
-	self 
-		assertMerge: #(a1 b1 d1)
-				with: #(a2 c1)
-				base: #(a1 c1 d1)
-				
-				gives: #(a2 b1)
-				conflicts: #()
-!
-
-testIdenticalModification
-	self
-		assertMerge: #(a2 b1)
-				with: #(a2 b1)
-				base: #(a1 b1)
-				
-				gives: #(a2 b1)
-				conflicts: #()
-!
-
-testLocalModifyRemoteRemove
-	self assertMerge: #(a2 b1)
-				with: #(b1)
-				base: #(a1 b1)
-				
-				gives: #(b1)
-				conflicts: #((removed a2)).
-				
-	self assertMerge: #(a1 b1)
-				with: #(b1)
-				base: #(a2 b1)
-				
-				gives: #(b1)
-				conflicts: #((removed a1)).
-!
-
-testLocalRemoveRemoteModify
-	self assertMerge: #(b1)
-				with: #(a1 b1)
-				base: #(a2 b1)
-				
-				gives: #(a1 b1)
-				conflicts: #((a1 removed)).
-
-	self assertMerge: #(b1)
-				with: #(a2 b1)
-				base: #(a1 b1)
-				
-				gives: #(a2 b1)
-				conflicts: #((a2 removed)).
-!
-
-testMultiPackageMerge
-	| merger |
-	conflicts := #().
-	merger := MCThreeWayMerger new.
-	merger addBaseSnapshot: (self snapshotWithElements: #(a1 b1)).
-	merger applyPatch: ((self snapshotWithElements: #()) patchRelativeToBase: (self snapshotWithElements: #(a1))).
-	merger applyPatch: ((self snapshotWithElements: #(a2 b1)) patchRelativeToBase: (self snapshotWithElements: #(b1))).
-	merger conflicts do: [:ea | self handleConflict: ea].
-	self assert: merger mergedSnapshot definitions hasElements: #(a2 b1).
-	self assert: conflicts isEmpty
-!
-
-testMultiPackageMerge2
-	| merger |
-	conflicts := #().
-	merger := MCThreeWayMerger new.
-	merger addBaseSnapshot: (self snapshotWithElements: #(a1 b1)).
-	merger applyPatch: ((self snapshotWithElements: #()) patchRelativeToBase: (self snapshotWithElements: #(a1))).
-	merger applyPatch: ((self snapshotWithElements: #(a1 b1)) patchRelativeToBase: (self snapshotWithElements: #(b1))).
-	merger conflicts do: [:ea | self handleConflict: ea].
-	self assert: merger mergedSnapshot definitions hasElements: #(a1 b1).
-	self assert: conflicts isEmpty
-!
-
-testMultiPackageMerge3
-	| merger |
-	conflicts := #().
-	merger := MCThreeWayMerger new.
-	merger addBaseSnapshot: (self snapshotWithElements: #(a1 b1)).
-	merger applyPatch: ((self snapshotWithElements: #(a1 b1)) patchRelativeToBase: (self snapshotWithElements: #(b1))).
-	merger applyPatch: ((self snapshotWithElements: #()) patchRelativeToBase: (self snapshotWithElements: #(a1))).
-	merger conflicts do: [:ea | self handleConflict: ea].
-	self assert: merger mergedSnapshot definitions hasElements: #(a1 b1).
-	self assert: conflicts isEmpty
-!
-
-testMultipleConflicts
-	self assertMerge: #(a1 b3 c1)
-				with: #(a1 b2 d1)
-				base: #(a1 b1 c2)
-				
-				gives: #(a1 b3 d1)
-				conflicts: #((removed c1) (b2 b3))
-
-!
-
-testSimultaneousModification
-	self assertMerge: #(a2)
-				with: #(a3)
-				base: #(a1)
-				
-				gives: #(a3)
-				conflicts: #((a3 a2)).
-!
-
-testSimultaneousRemove
-	self assertMerge: #(a1)
-				with: #(a1)
-				base: #(a1 b1)
-				
-				gives: #(a1)
-				conflicts: #()
-!
-
-testSubtractiveConflictlessMerge
-	self assertMerge: #(a1 b1)
-				with: #()
-				base: #(a1)
-				
-				gives: #(b1)
-				conflicts: #()
-! !
-
-!MCMergingTest class methodsFor:'documentation'!
-
-version
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCMergingTest.st,v 1.1 2011-08-20 12:03:03 cg Exp $'
-!
-
-version_CVS
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCMergingTest.st,v 1.1 2011-08-20 12:03:03 cg Exp $'
-!
-
-version_SVN
-    ^ '§Id: MCMergingTest.st 8 2010-09-12 17:15:52Z vranyj1 §'
-! !
--- a/MCMethodDefinitionTest.st	Thu Apr 30 21:53:12 2015 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,121 +0,0 @@
-"{ Package: 'stx:goodies/monticello' }"
-
-MCTestCase subclass:#MCMethodDefinitionTest
-	instanceVariableNames:'navigation isModified'
-	classVariableNames:''
-	poolDictionaries:''
-	category:'Monticello-Tests'
-!
-
-
-!MCMethodDefinitionTest methodsFor:'running'!
-
-ownPackage
-	^ MCWorkingCopy forPackage: (MCPackage named: 'Monticello')
-!
-
-setUp
-	navigation := (Smalltalk hasClassNamed: #SystemNavigation)
-		ifTrue: [(Smalltalk at: #SystemNavigation) new]
-		ifFalse: [Smalltalk].
-	isModified := self ownPackage modified.
-!
-
-tearDown
-	self restoreMocks.
-	(MCWorkingCopy forPackage: (MCPackage named: 'FooBarBaz')) unregister.
-	self class compile: 'override ^ 1' classified: 'mocks'.
-	self ownPackage modified: isModified
-! !
-
-!MCMethodDefinitionTest methodsFor:'testing'!
-
-__testRevertOldMethod
-        | definition changeRecord |
-        Object compile: 'yourself ^ self' classified: MCMockPackageInfo new methodCategoryPrefix.
-        definition := (MethodReference class: Object selector: #yourself) asMethodDefinition.
-        changeRecord := definition scanForPreviousVersion.
-        self assert: changeRecord notNil.
-        self assert: changeRecord category = 'accessing'.
-        changeRecord fileIn.
-
-    "Created: / 11-09-2010 / 18:47:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-testCannotLoad
-	| definition |
-	definition := self mockMethod: #kjahs87 class: 'NoSuchClass' source: 'kjahs87 ^self' meta: false.
-	self should: [definition load] raise: Error.
-	self assert: (navigation allImplementorsOf: #kjahs87) isEmpty
-!
-
-testComparison
-	|d1 d2 d3 d4 d5 |
-	d1 := self mockMethod: #one class: 'A' source: '1' meta: false.
-	d2 := self mockMethod: #one class: 'A' source: '2' meta: false.
-	d3 := self mockMethod: #one class: 'A' source: '1' meta: true.
-	d4 := self mockMethod: #two class: 'A' source: '1' meta: false.
-	d5 := self mockMethod: #two class: 'A' source: '1' meta: false.
-	
-	self assert: (d1 isRevisionOf: d2).
-	self deny: (d1 isSameRevisionAs: d2).
-	
-	self deny: (d1 isRevisionOf: d3).
-	self deny: (d1 isRevisionOf: d4).
-	
-	self assert: (d4 isSameRevisionAs: d5).
-!
-
-testLoadAndUnload
-	|definition|
-	definition := self mockMethod: #one class: 'MCMockClassA' source: 'one ^2' meta: false.
-	self assert: self mockInstanceA one = 1.
-	definition load.
-	self assert: self mockInstanceA one = 2.
-	definition unload.
-	self deny: (self mockInstanceA respondsTo: #one)
-!
-
-testPartiallyRevertOverrideMethod
-        | definition |
-        self class compile: 'override ^ 2' classified: '*foobarbaz'.
-        self class compile: 'override ^ 3' classified: self mockOverrideMethodCategory.
-        self class compile: 'override ^ 4' classified: self mockOverrideMethodCategory.
-        definition := (MethodReference class: self class selector: #override) asMethodDefinition.
-        self assert: definition isOverrideMethod.
-        "/TODO: Fix it later ;-)
-        "/self assert: self override = 4.
-        definition unload.
-        "/self assert: self override = 2.
-        "/self assert: (MethodReference class: self class selector: #override) category = '*foobarbaz'.
-
-    "Modified: / 11-09-2010 / 18:48:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-testRevertOverrideMethod
-        | definition |
-        self class compile: 'override ^ 2' classified: self mockOverrideMethodCategory.
-        definition := (MethodReference class: self class selector: #override) asMethodDefinition.
-        self assert: definition isOverrideMethod.
-        "/TODO: Fix it later
-        "/self assert: self override = 2.
-        definition unload.
-        "/self assert: self override = 1.
-        "/self assert: (MethodReference class: self class selector: #override) category = 'mocks'.
-
-    "Modified: / 11-09-2010 / 18:46:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-! !
-
-!MCMethodDefinitionTest class methodsFor:'documentation'!
-
-version
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCMethodDefinitionTest.st,v 1.1 2011-08-20 12:33:52 cg Exp $'
-!
-
-version_CVS
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCMethodDefinitionTest.st,v 1.1 2011-08-20 12:33:52 cg Exp $'
-!
-
-version_SVN
-    ^ '§Id: MCMethodDefinitionTest.st 27 2011-03-07 03:48:48Z vranyj1 §'
-! !
--- a/MCMockASubclass.st	Thu Apr 30 21:53:12 2015 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,37 +0,0 @@
-"{ Package: 'stx:goodies/monticello' }"
-
-MCMockClassA subclass:#MCMockASubclass
-	instanceVariableNames:'x'
-	classVariableNames:'Y'
-	poolDictionaries:''
-	category:'SCM-Monticello-Mocks'
-!
-
-MCMockASubclass comment:'nil
-'
-!
-
-
-!MCMockASubclass methodsFor:'as yet unclassified'!
-
-variables
-	^ x + Y + MCMockClassA
-!
-
-variables2
-	^ ivar + CVar
-! !
-
-!MCMockASubclass class methodsFor:'documentation'!
-
-version
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCMockASubclass.st,v 1.3 2012-09-11 21:23:42 cg Exp $'
-!
-
-version_CVS
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCMockASubclass.st,v 1.3 2012-09-11 21:23:42 cg Exp $'
-!
-
-version_SVN
-    ^ '§Id: MCMockASubclass.st 12 2010-09-15 13:13:22Z vranyj1 §'
-! !
--- a/MCMockClassA.st	Thu Apr 30 21:53:12 2015 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,96 +0,0 @@
-"{ Package: 'stx:goodies/monticello' }"
-
-MCMock subclass:#MCMockClassA
-	instanceVariableNames:'ivar'
-	classVariableNames:'CVar'
-	poolDictionaries:''
-	category:'SCM-Monticello-Mocks'
-!
-
-MCMockClassA comment:'This is a mock class. The Monticello tests manipulated it to simulate a developer modifying code in the image.
-'
-!
-
-
-!MCMockClassA class methodsFor:'as yet unclassified'!
-
-cVar
-	^ CVar
-!
-
-initialize
-	CVar := #initialized
-!
-
-one
-
-	^ 1
-!
-
-touchCVar
-	CVar := #touched
-! !
-
-!MCMockClassA methodsFor:'as yet classified'!
-
-d
-	^ 'd'
-! !
-
-!MCMockClassA methodsFor:'boolean'!
-
-falsehood
-	^ false
-!
-
-moreTruth
-
-	^ true
-!
-
-truth
-	^ true
-! !
-
-!MCMockClassA methodsFor:'drag''n''drop'!
-
-q
-! !
-
-!MCMockClassA methodsFor:'numeric'!
-
-a 
-	^ 'a2'
-!
-
-b
-	^ 'b1'
-!
-
-c
-	^ 'c1'
-!
-
-one
-	^ 1
-!
-
-two
-	^ 2
-! !
-
-!MCMockClassA class methodsFor:'documentation'!
-
-version
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCMockClassA.st,v 1.3 2012-09-11 21:23:46 cg Exp $'
-!
-
-version_CVS
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCMockClassA.st,v 1.3 2012-09-11 21:23:46 cg Exp $'
-!
-
-version_SVN
-    ^ '§Id: MCMockClassA.st 17 2010-10-13 12:07:52Z vranyj1 §'
-! !
-
-MCMockClassA initialize!
--- a/MCMockClassB.st	Thu Apr 30 21:53:12 2015 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,40 +0,0 @@
-"{ Package: 'stx:goodies/monticello' }"
-
-MCMock subclass:#MCMockClassB
-	instanceVariableNames:'ivarb'
-	classVariableNames:'CVar'
-	poolDictionaries:'MCMockAPoolDictionary'
-	category:'SCM-Monticello-Mocks'
-!
-
-MCMockClassB class instanceVariableNames:'ciVar'
-
-"
- No other class instance variables are inherited by this class.
-"
-!
-
-MCMockClassB comment:''
-!
-
-
-!MCMockClassB methodsFor:'numeric'!
-
-two
-
-	^ 2
-! !
-
-!MCMockClassB class methodsFor:'documentation'!
-
-version
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCMockClassB.st,v 1.3 2012-09-11 21:12:54 cg Exp $'
-!
-
-version_CVS
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCMockClassB.st,v 1.3 2012-09-11 21:12:54 cg Exp $'
-!
-
-version_SVN
-    ^ '§Id: MCMockClassB.st 27 2011-03-07 03:48:48Z vranyj1 §'
-! !
--- a/MCMockClassD.st	Thu Apr 30 21:53:12 2015 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,33 +0,0 @@
-"{ Package: 'stx:goodies/monticello' }"
-
-Object subclass:#MCMockClassD
-	instanceVariableNames:''
-	classVariableNames:''
-	poolDictionaries:''
-	category:'SCM-Monticello-Mocks'
-!
-
-MCMockClassD comment:'nil
-'
-!
-
-
-!MCMockClassD methodsFor:'as yet unclassified'!
-
-one
-	^ 1
-! !
-
-!MCMockClassD class methodsFor:'documentation'!
-
-version
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCMockClassD.st,v 1.3 2012-09-11 21:23:51 cg Exp $'
-!
-
-version_CVS
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCMockClassD.st,v 1.3 2012-09-11 21:23:51 cg Exp $'
-!
-
-version_SVN
-    ^ '§Id: MCMockClassD.st 12 2010-09-15 13:13:22Z vranyj1 §'
-! !
--- a/MCMockClassE.st	Thu Apr 30 21:53:12 2015 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,27 +0,0 @@
-"{ Package: 'stx:goodies/monticello' }"
-
-Object subclass:#MCMockClassE
-	instanceVariableNames:''
-	classVariableNames:''
-	poolDictionaries:''
-	category:'SCM-Monticello-Mocks'
-!
-
-MCMockClassE comment:'nil
-'
-!
-
-
-!MCMockClassE class methodsFor:'documentation'!
-
-version
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCMockClassE.st,v 1.3 2012-09-11 21:23:55 cg Exp $'
-!
-
-version_CVS
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCMockClassE.st,v 1.3 2012-09-11 21:23:55 cg Exp $'
-!
-
-version_SVN
-    ^ '§Id: MCMockClassE.st 12 2010-09-15 13:13:22Z vranyj1 §'
-! !
--- a/MCMockClassF.st	Thu Apr 30 21:53:12 2015 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,27 +0,0 @@
-"{ Package: 'stx:goodies/monticello' }"
-
-Object subclass:#MCMockClassF
-	instanceVariableNames:''
-	classVariableNames:'Foo'
-	poolDictionaries:''
-	category:'SCM-Monticello-Mocks'
-!
-
-MCMockClassF comment:'nil
-'
-!
-
-
-!MCMockClassF class methodsFor:'documentation'!
-
-version
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCMockClassF.st,v 1.3 2012-09-11 21:24:00 cg Exp $'
-!
-
-version_CVS
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCMockClassF.st,v 1.3 2012-09-11 21:24:00 cg Exp $'
-!
-
-version_SVN
-    ^ '§Id: MCMockClassF.st 12 2010-09-15 13:13:22Z vranyj1 §'
-! !
--- a/MCMockClassG.st	Thu Apr 30 21:53:12 2015 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,27 +0,0 @@
-"{ Package: 'stx:goodies/monticello' }"
-
-Object subclass:#MCMockClassG
-	instanceVariableNames:''
-	classVariableNames:''
-	poolDictionaries:''
-	category:'SCM-Monticello-Mocks'
-!
-
-MCMockClassG comment:'nil
-'
-!
-
-
-!MCMockClassG class methodsFor:'documentation'!
-
-version
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCMockClassG.st,v 1.3 2012-09-11 21:24:04 cg Exp $'
-!
-
-version_CVS
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCMockClassG.st,v 1.3 2012-09-11 21:24:04 cg Exp $'
-!
-
-version_SVN
-    ^ '§Id: MCMockClassG.st 28 2011-03-08 02:44:07Z vranyj1 §'
-! !
--- a/MCMockClassH.st	Thu Apr 30 21:53:12 2015 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,27 +0,0 @@
-"{ Package: 'stx:goodies/monticello' }"
-
-Object subclass:#MCMockClassH
-	instanceVariableNames:''
-	classVariableNames:''
-	poolDictionaries:''
-	category:'SCM-Monticello-Mocks'
-!
-
-MCMockClassH comment:'nil
-'
-!
-
-
-!MCMockClassH class methodsFor:'documentation'!
-
-version
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCMockClassH.st,v 1.3 2012-09-11 21:24:08 cg Exp $'
-!
-
-version_CVS
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCMockClassH.st,v 1.3 2012-09-11 21:24:08 cg Exp $'
-!
-
-version_SVN
-    ^ '§Id: MCMockClassH.st 28 2011-03-08 02:44:07Z vranyj1 §'
-! !
--- a/MCMockClassI.st	Thu Apr 30 21:53:12 2015 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,27 +0,0 @@
-"{ Package: 'stx:goodies/monticello' }"
-
-Object subclass:#MCMockClassI
-	instanceVariableNames:''
-	classVariableNames:''
-	poolDictionaries:''
-	category:'SCM-Monticello-Mocks'
-!
-
-MCMockClassI comment:'nil
-'
-!
-
-
-!MCMockClassI class methodsFor:'documentation'!
-
-version
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCMockClassI.st,v 1.3 2012-09-11 21:24:12 cg Exp $'
-!
-
-version_CVS
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCMockClassI.st,v 1.3 2012-09-11 21:24:12 cg Exp $'
-!
-
-version_SVN
-    ^ '§Id: MCMockClassI.st 28 2011-03-08 02:44:07Z vranyj1 §'
-! !
--- a/MCOrganizationTest.st	Thu Apr 30 21:53:12 2015 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,55 +0,0 @@
-"{ Package: 'stx:goodies/monticello' }"
-
-MCTestCase subclass:#MCOrganizationTest
-	instanceVariableNames:''
-	classVariableNames:''
-	poolDictionaries:''
-	category:'Monticello-Tests'
-!
-
-
-!MCOrganizationTest methodsFor:'as yet unclassified'!
-
-testReordering
-        |dec cats newCats |
-        dec := MCOrganizationDefinition categories: #(A B C).
-        cats := #(X Y B Z C A Q).
-        newCats := dec reorderCategories: cats original: #(B C A).
-        "/No need to reorganize cats"
-        self assert: newCats asArray = cats"#(X Y A B C Z Q)".
-
-    "Modified: / 11-09-2010 / 18:58:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-testReorderingWithNoCategoriesInVersion
-	|dec cats newCats |
-	dec := MCOrganizationDefinition categories: #().
-	cats := #(X Y B Z C A Q).
-	newCats := dec reorderCategories: cats original: #().
-	self assert: newCats asArray = cats.
-!
-
-testReorderingWithRemovals
-        |dec cats newCats |
-        dec := MCOrganizationDefinition categories: #(A B C).
-        cats := #(X Y B Z C A Q).
-        newCats := dec reorderCategories: cats original: #(Y B C A Q).
-        "/No need to reogranize cats"
-        self assert: newCats asArray = newCats "#(X A B C Z)".
-
-    "Modified: / 11-09-2010 / 18:59:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-! !
-
-!MCOrganizationTest class methodsFor:'documentation'!
-
-version
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCOrganizationTest.st,v 1.1 2011-08-20 12:27:49 cg Exp $'
-!
-
-version_CVS
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCOrganizationTest.st,v 1.1 2011-08-20 12:27:49 cg Exp $'
-!
-
-version_SVN
-    ^ '§Id: MCOrganizationTest.st 7 2010-09-12 07:18:55Z vranyj1 §'
-! !
--- a/MCPackageTest.st	Thu Apr 30 21:53:12 2015 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,41 +0,0 @@
-"{ Package: 'stx:goodies/monticello' }"
-
-MCTestCase subclass:#MCPackageTest
-	instanceVariableNames:''
-	classVariableNames:''
-	poolDictionaries:''
-	category:'Monticello-Tests'
-!
-
-
-!MCPackageTest methodsFor:'running'!
-
-tearDown
-	self mockSnapshot install
-! !
-
-!MCPackageTest methodsFor:'tests'!
-
-testUnload
-	| mock |
-	self mockPackage unload.
-	self deny: (Smalltalk hasClassNamed: #MCMockClassA).
-	self deny: (MCSnapshotTest includesSelector: #mockClassExtension).
-
-	mock := (Smalltalk at: #MCMock).
-	self assert: (mock subclasses detect: [:c | c name = #MCMockClassA] ifNone: []) isNil
-! !
-
-!MCPackageTest class methodsFor:'documentation'!
-
-version
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCPackageTest.st,v 1.1 2011-08-20 12:56:27 cg Exp $'
-!
-
-version_CVS
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCPackageTest.st,v 1.1 2011-08-20 12:56:27 cg Exp $'
-!
-
-version_SVN
-    ^ '§Id: MCPackageTest.st 5 2010-08-29 07:30:29Z vranyj1 §'
-! !
--- a/MCPatchTest.st	Thu Apr 30 21:53:12 2015 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,45 +0,0 @@
-"{ Package: 'stx:goodies/monticello' }"
-
-MCTestCase subclass:#MCPatchTest
-	instanceVariableNames:'patch'
-	classVariableNames:''
-	poolDictionaries:''
-	category:'Monticello-Tests'
-!
-
-
-!MCPatchTest methodsFor:'as yet unclassified'!
-
-setUp
-	|rev1 rev2|
-	rev1 :=  MCSnapshotResource takeSnapshot.
-	self change: #one toReturn: 2.
-	rev2 :=  MCSnapshotResource takeSnapshot.
-	patch := rev2 patchRelativeToBase: rev1.
-	self change: #one toReturn: 1.
-!
-
-tearDown
-	self restoreMocks
-!
-
-testPatchContents
-	self assert: patch operations size = 1.
-	self assert: patch operations first isModification.
-	self assert: patch operations first definition selector = #one.
-
-! !
-
-!MCPatchTest class methodsFor:'documentation'!
-
-version
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCPatchTest.st,v 1.1 2011-08-20 12:17:47 cg Exp $'
-!
-
-version_CVS
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCPatchTest.st,v 1.1 2011-08-20 12:17:47 cg Exp $'
-!
-
-version_SVN
-    ^ '§Id: MCPatchTest.st 5 2010-08-29 07:30:29Z vranyj1 §'
-! !
--- a/MCRepositoryInspector.st	Thu Apr 30 21:53:12 2015 +0200
+++ b/MCRepositoryInspector.st	Sun May 10 05:53:16 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/monticello' }"
 
+"{ NameSpace: Smalltalk }"
+
 MCVersionInspector subclass:#MCRepositoryInspector
 	instanceVariableNames:'repository packages versions loaded selectedPackage
 		selectedVersion'
@@ -122,3 +124,4 @@
 version
     ^ '$Header: /cvs/stx/stx/goodies/monticello/MCRepositoryInspector.st,v 1.2 2012-09-11 21:15:04 cg Exp $'
 ! !
+
--- a/MCRepositoryTest.st	Thu Apr 30 21:53:12 2015 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,125 +0,0 @@
-"{ Package: 'stx:goodies/monticello' }"
-
-MCTestCase subclass:#MCRepositoryTest
-	instanceVariableNames:'repository ancestors'
-	classVariableNames:''
-	poolDictionaries:''
-	category:'Monticello-Tests'
-!
-
-
-!MCRepositoryTest class methodsFor:'as yet unclassified'!
-
-isAbstract
-	^ self = MCRepositoryTest
-! !
-
-!MCRepositoryTest methodsFor:'accessing'!
-
-snapshotAt: aVersionInfo
-	^ (repository versionWithInfo: aVersionInfo) snapshot
-! !
-
-!MCRepositoryTest methodsFor:'actions'!
-
-addVersion: aVersion
-	self subclassResponsibility 
-!
-
-addVersionWithSnapshot: aSnapshot name: aString
-	| version |
-	version := self versionWithSnapshot: aSnapshot name: aString.
-	self addVersion: version.
-	^ version info
-!
-
-saveSnapshot1
-	^ self saveSnapshot: self snapshot1 named: 'rev1'
-!
-
-saveSnapshot2
-	^ self saveSnapshot: self snapshot2 named: 'rev2'
-!
-
-saveSnapshot: aSnapshot named: aString
-	| version |
-	version := self versionWithSnapshot: aSnapshot name: aString.
-	repository storeVersion: version.
-	^ version info
-	
-! !
-
-!MCRepositoryTest methodsFor:'asserting'!
-
-assertMissing: aVersionInfo
-	self assert: (repository versionWithInfo: aVersionInfo) isNil
-!
-
-assertVersionInfos: aCollection
-	self assert: repository allVersionInfos asSet = aCollection asSet
-! !
-
-!MCRepositoryTest methodsFor:'building'!
-
-snapshot1
-	^ (MCSnapshot fromDefinitions: (Array with: (MCOrganizationDefinition categories: #('y'))))
-!
-
-snapshot2
-	^ (MCSnapshot fromDefinitions: (Array with: (MCOrganizationDefinition categories: #('x'))))
-!
-
-versionWithSnapshot: aSnapshot name: aString
-	| info |
-	info := self mockVersionInfo: aString. 
-	^ MCVersion 
-		package: (MCPackage new name: aString)
-		info: info
-		snapshot: aSnapshot
-! !
-
-!MCRepositoryTest methodsFor:'tests'!
-
-testAddAndLoad
-	| node |
-	node := self addVersionWithSnapshot: self snapshot1 name: 'rev1'.
-	self assert: (self snapshotAt: node) = self snapshot1.
-
-!
-
-testIncludesName
-	self deny: (repository includesVersionNamed: 'MonticelloTest-xxx.1-rev1').
-	self saveSnapshot1.
-	self assert: (repository includesVersionNamed: 'MonticelloTest-xxx.1-rev1').
-	self deny: (repository includesVersionNamed: 'MonticelloTest-xxx.1-rev2').
-	self saveSnapshot2.
-	self assert:  (repository includesVersionNamed: 'MonticelloTest-xxx.1-rev2').
-!
-
-testLoadMissingNode
-	| node |
-	node := MCVersionInfo new.
-	self assertMissing: node
-!
-
-testStoreAndLoad
-	| node node2 |
-	node := self saveSnapshot1.
-	node2 := self saveSnapshot2.
-	self assert: (self snapshotAt: node) = self snapshot1.
-	self assert: (self snapshotAt: node2) = self snapshot2.
-! !
-
-!MCRepositoryTest class methodsFor:'documentation'!
-
-version
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCRepositoryTest.st,v 1.2 2011-08-20 12:06:01 cg Exp $'
-!
-
-version_CVS
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCRepositoryTest.st,v 1.2 2011-08-20 12:06:01 cg Exp $'
-!
-
-version_SVN
-    ^ '§Id: MCRepositoryTest.st 5 2010-08-29 07:30:29Z vranyj1 §'
-! !
--- a/MCSMCacheRepository.st	Thu Apr 30 21:53:12 2015 +0200
+++ b/MCSMCacheRepository.st	Sun May 10 05:53:16 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/monticello' }"
 
+"{ NameSpace: Smalltalk }"
+
 MCFileBasedRepository subclass:#MCSMCacheRepository
 	instanceVariableNames:'smCache'
 	classVariableNames:''
@@ -104,3 +106,4 @@
 version
     ^ '$Header: /cvs/stx/stx/goodies/monticello/MCSMCacheRepository.st,v 1.2 2012-09-11 21:14:13 cg Exp $'
 ! !
+
--- a/MCSaveVersionDialog.st	Thu Apr 30 21:53:12 2015 +0200
+++ b/MCSaveVersionDialog.st	Sun May 10 05:53:16 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/monticello' }"
 
+"{ NameSpace: Smalltalk }"
+
 MCTool subclass:#MCSaveVersionDialog
 	instanceVariableNames:'name message'
 	classVariableNames:''
@@ -67,3 +69,4 @@
 version
     ^ '$Header: /cvs/stx/stx/goodies/monticello/MCSaveVersionDialog.st,v 1.2 2012-09-11 21:14:47 cg Exp $'
 ! !
+
--- a/MCScannerTest.st	Thu Apr 30 21:53:12 2015 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,57 +0,0 @@
-"{ Package: 'stx:goodies/monticello' }"
-
-MCTestCase subclass:#MCScannerTest
-	instanceVariableNames:''
-	classVariableNames:''
-	poolDictionaries:''
-	category:'Monticello-Tests'
-!
-
-
-!MCScannerTest methodsFor:'asserting'!
-
-assertScans: anArray
-        self assert: (MCScanner scan: anArray storeString readStream) = anArray
-
-    "Modified: / 11-09-2010 / 22:08:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-! !
-
-!MCScannerTest methodsFor:'tests'!
-
-test1
-	self assertScans: #(a '23' (x))
-!
-
-test2
-	self assertScans: 'it''s alive'
-!
-
-test3
-	self assert: (MCScanner scan: '(a #b c)' readStream) = #(a #b c)
-!
-
-test4
-	self assertScans: #(a '23' (x () ')''q' y12)).
-!
-
-test5
-	self assertScans: #((a) b)
-!
-
-test6
-	self should: [MCScanner scan: '(a b' readStream] raise: Error
-! !
-
-!MCScannerTest class methodsFor:'documentation'!
-
-version
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCScannerTest.st,v 1.1 2011-08-20 12:34:32 cg Exp $'
-!
-
-version_CVS
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCScannerTest.st,v 1.1 2011-08-20 12:34:32 cg Exp $'
-!
-
-version_SVN
-    ^ '§Id: MCScannerTest.st 7 2010-09-12 07:18:55Z vranyj1 §'
-! !
--- a/MCSerializationTest.st	Thu Apr 30 21:53:12 2015 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,131 +0,0 @@
-"{ Package: 'stx:goodies/monticello' }"
-
-MCTestCase subclass:#MCSerializationTest
-	instanceVariableNames:''
-	classVariableNames:''
-	poolDictionaries:''
-	category:'Monticello-Tests'
-!
-
-
-!MCSerializationTest methodsFor:'asserting'!
-
-assertClass: readerClass providesServices: labels
-	| services suffix |
-	suffix := readerClass extension.
-	self assert: (FileList isReaderNamedRegistered: readerClass name).
-	services := readerClass fileReaderServicesForFile: 'foo' suffix: suffix.
-	self assert: ((services collect: [:service | service buttonLabel]) includesAllOf: labels)
-!
-
-assertDependenciesMatchWith:writerClass 
-    |stream readerClass expected actual|
-
-    readerClass := writerClass readerClass.
-    expected := self mockVersionWithDependencies.
-    stream := RWBinaryOrTextStream on:ByteArray new.
-    writerClass fileOut:expected on:stream.
-    actual := (readerClass on:stream reset) dependencies.
-    self assert:actual = expected dependencies.
-
-    "Modified: / 12-09-2010 / 13:16:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-assertExtensionProvidedBy: aClass
-	self shouldnt: [aClass readerClass extension] raise: Exception.
-!
-
-assertSnapshotsMatchWith:writerClass 
-    |readerClass expected stream actual|
-
-    readerClass := writerClass readerClass.
-    expected := self mockSnapshot.
-    stream := RWBinaryOrTextStream on:String new.
-    (writerClass on:stream) writeSnapshot:expected.
-    actual := readerClass snapshotFromStream:stream reset.
-    self assertSnapshot:actual matches:expected.
-
-    "Modified: / 12-09-2010 / 13:17:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-assertVersionInfosMatchWith:writerClass 
-    |stream readerClass expected actual|
-
-    readerClass := writerClass readerClass.
-    expected := self mockVersion.
-    stream := RWBinaryOrTextStream on:ByteArray new.
-    writerClass fileOut:expected on:stream.
-    actual := readerClass versionInfoFromStream:stream reset.
-    self assert:actual = expected info.
-
-    "Modified: / 12-09-2010 / 13:15:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-assertVersionsMatchWith:writerClass 
-    |stream readerClass expected actual|
-
-    readerClass := writerClass readerClass.
-    expected := self mockVersion.
-    stream := RWBinaryOrTextStream on:ByteArray new.
-    writerClass fileOut:expected on:stream.
-    actual := readerClass versionFromStream:stream reset.
-    self assertVersion:actual matches:expected.
-
-    "Modified: / 11-09-2010 / 19:42:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-! !
-
-!MCSerializationTest methodsFor:'mocks'!
-
-mockDiffyVersion
-	| repos workingCopy base next |
-	repos := MCDictionaryRepository new.
-	workingCopy := MCWorkingCopy forPackage: self mockPackage.
-	workingCopy repositoryGroup addRepository: repos.
-	MCRepositoryGroup default removeRepository: repos.
-	base := self mockVersion.
-	repos storeVersion: base.
-	self change: #a toReturn: 'a2'.
-	next := self mockVersionWithAncestor: base.
-	^ next asDiffAgainst: base	
-! !
-
-!MCSerializationTest methodsFor:'testing'!
-
-__testMcdSerialization
-    |stream expected actual|
-
-    expected := self mockDiffyVersion.
-    stream := RWBinaryOrTextStream on:ByteArray new.
-    MCMcdWriter fileOut:expected on:stream.
-    actual := MCMcdReader versionFromStream:stream reset.
-    self assertVersion:actual matches:expected.
-
-    "Created: / 11-09-2010 / 19:42:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-__testStSerialization
-        self assertSnapshotsMatchWith: MCStWriter.
-
-    "Created: / 12-09-2010 / 15:26:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-testMczSerialization
-	self assertVersionsMatchWith: MCMczWriter.
-	self assertExtensionProvidedBy: MCMczWriter.
-	self assertVersionInfosMatchWith: MCMczWriter.
-	self assertDependenciesMatchWith: MCMczWriter.
-! !
-
-!MCSerializationTest class methodsFor:'documentation'!
-
-version
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCSerializationTest.st,v 1.1 2011-08-20 12:27:19 cg Exp $'
-!
-
-version_CVS
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCSerializationTest.st,v 1.1 2011-08-20 12:27:19 cg Exp $'
-!
-
-version_SVN
-    ^ '§Id: MCSerializationTest.st 8 2010-09-12 17:15:52Z vranyj1 §'
-! !
--- a/MCSnapshotBrowser.st	Thu Apr 30 21:53:12 2015 +0200
+++ b/MCSnapshotBrowser.st	Sun May 10 05:53:16 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/monticello' }"
 
+"{ NameSpace: Smalltalk }"
+
 MCCodeTool subclass:#MCSnapshotBrowser
 	instanceVariableNames:'categorySelection classSelection protocolSelection
 		methodSelection switch'
@@ -382,3 +384,4 @@
 version
     ^ '$Header: /cvs/stx/stx/goodies/monticello/MCSnapshotBrowser.st,v 1.2 2012-09-11 21:14:41 cg Exp $'
 ! !
+
--- a/MCSnapshotBrowserTest.st	Thu Apr 30 21:53:12 2015 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,334 +0,0 @@
-"{ Package: 'stx:goodies/monticello' }"
-
-MCTestCase subclass:#MCSnapshotBrowserTest
-	instanceVariableNames:'model morph'
-	classVariableNames:''
-	poolDictionaries:''
-	category:'Monticello-Tests'
-!
-
-
-!MCSnapshotBrowserTest methodsFor:'asserting'!
-
-assertAListIncludes: anArrayOfStrings
-	self listMorphs 
-			detect: [:m | m getList includesAllOf: anArrayOfStrings]
-			ifNone: [self assert: false].
-!
-
-assertAListMatches: strings
-	| listMorphs list |
-	listMorphs := self listMorphs.
-	listMorphs 
-		detect: [:m | list := m getList. (list size = strings size) and: [list includesAllOf: strings]]
-		ifNone: [self assert: false].
-!
-
-assertButtonExists: aString
-	self buttonMorphs detect: [:m | m label = aString] ifNone: [self assert: false].
-				
-!
-
-assertButtonOn: aString
-	self assert: (self findButtonWithLabel: aString) getModelState.
-	
-!
-
-assertTextIs: aString
-	self assert: self textMorph contents = aString.
-!
-
-denyAListHasSelection: aString
-	| found |
-	found := true.
-	self listMorphs 
-			detect: [:m | m selection = aString]
-			ifNone: [found := false].
-	self deny: found.
-!
-
-denyAListIncludesAnyOf: anArrayOfStrings
-	| found |
-	found := true.
-	self listMorphs 
-			detect: [:m | m getList includesAnyOf: anArrayOfStrings]
-			ifNone: [found := false].
-	self deny: found.
-!
-
-denyButtonOn: aString
-	self deny: (self findButtonWithLabel: aString) getModelState.
-	
-! !
-
-!MCSnapshotBrowserTest methodsFor:'morphic'!
-
-annotationTextMorph
-	^ (self morphsOfClass: TextMorph) first
-!
-
-buttonMorphs
-	^ self morphsOfClass: PluggableButtonMorph
-!
-
-findButtonWithLabel: aString
-	^ self buttonMorphs detect: [:m | m label = aString]
-!
-
-findListContaining: aString
-	^ self listMorphs detect: [:m | m getList includes: aString]
-!
-
-listMorphs
-	^ self morphsOfClass: PluggableListMorph
-!
-
-morphsOfClass: aMorphClass
-	| morphs |
-	morphs := OrderedCollection new.
-	morph allMorphsDo: [:m | (m isKindOf: aMorphClass) ifTrue: [morphs add: m]].
-	^ morphs
-!
-
-textMorph
-	^ (self morphsOfClass: TextMorph) last
-! !
-
-!MCSnapshotBrowserTest methodsFor:'private'!
-
-allCategories
-	^ Array with: model extensionsCategory with: self mockCategoryName.
-!
-
-allMethods
-	^ MCSnapshotResource current definitions
-		select: [:def | def isMethodDefinition]
-		thenCollect: [:def | def selector]		
-!
-
-allProtocols
-	^ MCSnapshotResource current definitions
-		select: [:def | def isMethodDefinition]
-		thenCollect: [:def | def category]		
-!
-
-classABooleanMethods
-	^ #(falsehood moreTruth truth)
-!
-
-classAClassProtocols
-	^ self protocolsForClass: self mockClassA class.
-!
-
-classAComment
-	^ self mockClassA organization classComment.
-!
-
-classADefinitionString
-	^ self mockClassA definition
-!
-
-classAProtocols
-	^ self protocolsForClass: self mockClassA.
-!
-
-definedClasses
-	^ MCSnapshotResource current definitions 
-		select: [:def | def isClassDefinition] 
-		thenCollect: [:def | def className].
-!
-
-falsehoodMethodSource
-	^ 'falsehood
-	^ false'
-!
-
-protocolsForClass: aClass
-	| protocols |
-	protocols := aClass organization categories.
-	protocols size > 1 ifTrue: [protocols := protocols copyWith: '-- all --'].
-	^ protocols.
-! !
-
-!MCSnapshotBrowserTest methodsFor:'running'!
-
-setUp
-	model := MCSnapshotBrowser forSnapshot: MCSnapshotResource current snapshot.
-	morph := model buildWindow.
-! !
-
-!MCSnapshotBrowserTest methodsFor:'selecting'!
-
-selectMockClassA
-	self clickOnListItem: self mockCategoryName.
-	self clickOnListItem: 'MCMockClassA'.
-	
-! !
-
-!MCSnapshotBrowserTest methodsFor:'simulating'!
-
-clickOnButton: aString
-	(self findButtonWithLabel: aString) performAction.
-!
-
-clickOnListItem: aString
-	| listMorph |
-	listMorph := self findListContaining: aString.
-	listMorph changeModelSelection: (listMorph getList indexOf: aString).
-! !
-
-!MCSnapshotBrowserTest methodsFor:'testing'!
-
-testAnnotationPane
-	| oldPref |
-	oldPref := Preferences annotationPanes.
-
-	Preferences disable: #annotationPanes.
-	morph := model buildWindow.
-	self assert: (self morphsOfClass: TextMorph) size = 1.
-
-	Preferences enable: #annotationPanes.
-	morph := model buildWindow.
-	self assert: (self morphsOfClass: TextMorph) size = 2.
-
-	Preferences setPreference: #annotationPanes toValue: oldPref
-!
-
-testButtonMutex
-	self assertButtonOn: 'instance'.
-	self denyButtonOn: '?'.
-	self denyButtonOn: 'class'.
-	
-	self clickOnButton: '?'.
-	self assertButtonOn: '?'.
-	self denyButtonOn: 'instance'.
-	self denyButtonOn: 'class'.
-	
-	self clickOnButton: 'class'.
-	self assertButtonOn: 'class'.
-	self denyButtonOn: '?'.
-	self denyButtonOn: 'instance'.
-
-!
-
-testCategorySelected
-	self clickOnListItem: self mockCategoryName.
-	
-	self assertAListMatches: self allCategories.
-	self assertAListMatches: self definedClasses.
-	self denyAListIncludesAnyOf: self allProtocols.
-	self denyAListIncludesAnyOf: self allMethods.
-	self assertTextIs: ''.
-!
-
-testClassSelected
-	self selectMockClassA.
-	
-	self assertAListMatches: self allCategories.
-	self assertAListMatches: self definedClasses.
-	self assertAListMatches: self classAProtocols.
-	self denyAListIncludesAnyOf: self allMethods.
-	self assertTextIs: self classADefinitionString.
-!
-
-testClassSideClassSelected
-	self clickOnButton: 'class'.
-	self selectMockClassA.
-	
-	self assertAListMatches: self allCategories.
-	self assertAListMatches: self definedClasses.
-	self assertAListMatches: self classAClassProtocols.
-	self denyAListIncludesAnyOf: self allMethods.
-	self assertTextIs: self classADefinitionString.
-!
-
-testComment
-	self clickOnButton: '?'.
-	self assertTextIs: ''.
-	
-	self clickOnListItem: self mockCategoryName.
-	self assertTextIs: ''.
-	
-	self clickOnListItem: 'MCMockClassA'.
-	self assertTextIs: self classAComment.
-!
-
-testFourColumns
-	self assert: self listMorphs size = 4.
-!
-
-testMethodIsCleared
-	self clickOnListItem: self mockCategoryName.
-	self clickOnListItem: 'MCMockClassA'.
-	self clickOnListItem: 'boolean'.
-	self clickOnListItem: 'falsehood'.
-	self clickOnListItem: '-- all --'.
-	
-	self denyAListHasSelection: 'falsehood'.
-!
-
-testMethodSelected
-	self clickOnListItem: self mockCategoryName.
-	self clickOnListItem: 'MCMockClassA'.
-	self clickOnListItem: 'boolean'.
-	self clickOnListItem: 'falsehood'.
-	
-	self assertAListMatches: self allCategories.
-	self assertAListMatches: self definedClasses.
-	self assertAListMatches: self classAProtocols.
-	self assertAListMatches: self classABooleanMethods.
-	self assertTextIs: self falsehoodMethodSource.
-!
-
-testNoSelection
-	self assertAListMatches: self allCategories.
-	self denyAListIncludesAnyOf: self definedClasses.
-	self denyAListIncludesAnyOf: self allProtocols.
-	self denyAListIncludesAnyOf: self allMethods.
-	self assertTextIs: ''.
-!
-
-testProtocolIsCleared
-	self clickOnListItem: self mockCategoryName.
-	self clickOnListItem: 'MCMockASubclass'.
-	self clickOnListItem: 'as yet unclassified'.
-	self clickOnListItem: 'MCMockClassA'.
-	
-	self denyAListHasSelection: 'as yet unclassified'.
-!
-
-testProtocolSelected
-	self clickOnListItem: self mockCategoryName.
-	self clickOnListItem: 'MCMockClassA'.
-	self clickOnListItem: 'boolean'.
-	
-	self assertAListMatches: self allCategories.
-	self assertAListMatches: self definedClasses.
-	self assertAListMatches: self classAProtocols.
-	self assertAListMatches: self classABooleanMethods.
-	self assertTextIs: ''.		
-!
-
-testTextPane
-	self shouldnt: [self textMorph] raise: Exception.
-!
-
-testThreeButtons
-	self assertButtonExists: 'instance'.
-	self assertButtonExists: '?'.
-	self assertButtonExists: 'class'.
-! !
-
-!MCSnapshotBrowserTest class methodsFor:'documentation'!
-
-version
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCSnapshotBrowserTest.st,v 1.1 2011-08-20 12:34:50 cg Exp $'
-!
-
-version_CVS
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCSnapshotBrowserTest.st,v 1.1 2011-08-20 12:34:50 cg Exp $'
-!
-
-version_SVN
-    ^ '§Id: MCSnapshotBrowserTest.st 5 2010-08-29 07:30:29Z vranyj1 §'
-! !
--- a/MCSnapshotResource.st	Thu Apr 30 21:53:12 2015 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,51 +0,0 @@
-"{ Package: 'stx:goodies/monticello' }"
-
-TestResource subclass:#MCSnapshotResource
-	instanceVariableNames:'snapshot'
-	classVariableNames:''
-	poolDictionaries:''
-	category:'Monticello-Tests'
-!
-
-
-!MCSnapshotResource class methodsFor:'as yet unclassified'!
-
-mockPackage
-	^ (MCPackage new name: self mockPackageName)
-!
-
-mockPackageName
-	^ MCMockPackageInfo new packageName
-!
-
-takeSnapshot
-	^ self mockPackage snapshot
-! !
-
-!MCSnapshotResource methodsFor:'as yet unclassified'!
-
-definitions
-	^ snapshot definitions
-!
-
-setUp
-	snapshot := self class takeSnapshot.
-!
-
-snapshot
-	^ snapshot
-! !
-
-!MCSnapshotResource class methodsFor:'documentation'!
-
-version
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCSnapshotResource.st,v 1.1 2011-08-20 12:24:47 cg Exp $'
-!
-
-version_CVS
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCSnapshotResource.st,v 1.1 2011-08-20 12:24:47 cg Exp $'
-!
-
-version_SVN
-    ^ '§Id: MCSnapshotResource.st 5 2010-08-29 07:30:29Z vranyj1 §'
-! !
--- a/MCSnapshotTest.st	Thu Apr 30 21:53:12 2015 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,56 +0,0 @@
-"{ Package: 'stx:goodies/monticello' }"
-
-MCTestCase subclass:#MCSnapshotTest
-	instanceVariableNames:'snapshot'
-	classVariableNames:''
-	poolDictionaries:''
-	category:'Monticello-Tests'
-!
-
-
-!MCSnapshotTest methodsFor:'*monticello-mocks'!
-
-mockClassExtension
-! !
-
-!MCSnapshotTest methodsFor:'running'!
-
-setUp
-	snapshot :=  self mockSnapshot.
-! !
-
-!MCSnapshotTest methodsFor:'tests'!
-
-testCreation
-	|d|
-	d :=  self mockSnapshot definitions.
-	self assert: (d anySatisfy: [:ea | ea isClassDefinition and: [ea className = #MCMockClassA]]).
-	self assert: (d anySatisfy: [:ea | ea isMethodDefinition and: [ea selector = #mockClassExtension]]).
-	self assert: (d allSatisfy: [:ea | ea isClassDefinition not or: [ea category endsWith: 'Mocks']]).
-	
-!
-
-testInstanceReuse
-	| x m n y |
-	x := (MCPackage new name: self mockCategoryName) snapshot.
-	Smalltalk garbageCollect.
-	n := MCDefinition allSubInstances size.
-	y := (MCPackage new name: self mockCategoryName) snapshot.
-	Smalltalk garbageCollect.
-	m := MCDefinition allSubInstances size.
-	self assert: m = n
-! !
-
-!MCSnapshotTest class methodsFor:'documentation'!
-
-version
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCSnapshotTest.st,v 1.1 2011-08-20 13:15:34 cg Exp $'
-!
-
-version_CVS
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCSnapshotTest.st,v 1.1 2011-08-20 13:15:34 cg Exp $'
-!
-
-version_SVN
-    ^ '§Id: MCSnapshotTest.st 5 2010-08-29 07:30:29Z vranyj1 §'
-! !
--- a/MCStReaderTest.st	Thu Apr 30 21:53:12 2015 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,88 +0,0 @@
-"{ Package: 'stx:goodies/monticello' }"
-
-MCTestCase subclass:#MCStReaderTest
-	instanceVariableNames:''
-	classVariableNames:''
-	poolDictionaries:''
-	category:'Monticello-Tests'
-!
-
-
-!MCStReaderTest methodsFor:'as yet unclassified'!
-
-commentWithStyle
-	^ '!!AEDesc commentStamp: ''<historical>'' prior: 0!!
-I represent an Apple Event Descriptor.  I am a low-level representation of Apple Event (and hence Applescript) information.  For further Information, see Apple''s Inside Macintosh: Interapplication Communications, at
-
-	http://developer.apple.com/techpubs/mac/IAC/IAC-2.html.
-
-Essentially, I represent a record comprising a one-word "string" (treating the word as fourbyte characters) representing a data type, followed by a pointer to a pointer (a handle) to the data I represent.  Care must be taken to assure that the Handle data is disposed after use, or memory leaks result.  At this time, I make no effort to do this automatically through finalization.!!
-]style[(218 54 384)f1,f1Rhttp://developer.apple.com/techpubs/mac/IAC/IAC-2.html;,f1!!
-'
-!
-
-commentWithoutStyle
-	^ '
-CharacterScanner subclass: #CanvasCharacterScanner
-	instanceVariableNames: ''canvas fillBlt foregroundColor runX lineY ''
-	classVariableNames: ''''
-	poolDictionaries: ''''
-	category: ''Morphic-Support''!!
-
-!!CanvasCharacterScanner commentStamp: ''<historical>'' prior: 0!!
-A displaying scanner which draws its output to a Morphic canvas.!!
-
-!!CanvasCharacterScanner methodsFor: ''stop conditions'' stamp: ''ar 12/15/2001 23:27''!!
-setStopConditions
-	"Set the font and the stop conditions for the current run."
-
-	self setFont.
-	stopConditions
-		at: Space asciiValue + 1
-		put: (alignment = Justified ifTrue: [#paddedSpace])!! !!'
-!
-
-methodWithStyle
-	^ '!!EventHandler methodsFor: ''copying'' stamp: ''tk 1/22/2001 17:39''!!
-veryDeepInner: deepCopier
-	"ALL fields are weakly copied.  Can''t duplicate an object by duplicating a button that activates it.  See DeepCopier."
-
-	super veryDeepInner: deepCopier.
-	"just keep old pointers to all fields"
-	clickRecipient := clickRecipient.!!
-]style[(25 108 10 111)f1b,f1,f1LDeepCopier Comment;,f1!! !!
-
-'
-!
-
-testCommentWithStyle
-	| reader |
-	reader := MCStReader on: self commentWithStyle readStream.
-	reader definitions
-!
-
-testCommentWithoutStyle
-	| reader |
-	reader := MCStReader on: self commentWithoutStyle readStream.
-	self assert: (reader definitions anySatisfy: [:ea | ea isMethodDefinition]).
-!
-
-testMethodWithStyle
-	| reader |
-	reader := MCStReader on: self methodWithStyle readStream.
-	self assert: reader definitions first isMethodDefinition.
-! !
-
-!MCStReaderTest class methodsFor:'documentation'!
-
-version
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCStReaderTest.st,v 1.1 2011-08-20 12:21:03 cg Exp $'
-!
-
-version_CVS
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCStReaderTest.st,v 1.1 2011-08-20 12:21:03 cg Exp $'
-!
-
-version_SVN
-    ^ '§Id: MCStReaderTest.st 5 2010-08-29 07:30:29Z vranyj1 §'
-! !
--- a/MCStWriterTest.st	Thu Apr 30 21:53:12 2015 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,237 +0,0 @@
-"{ Package: 'stx:goodies/monticello' }"
-
-MCTestCase subclass:#MCStWriterTest
-	instanceVariableNames:'stream writer'
-	classVariableNames:''
-	poolDictionaries:''
-	category:'Monticello-Tests'
-!
-
-
-!MCStWriterTest methodsFor:'asserting'!
-
-assertAllChunksAreWellFormed
-	stream reset.
-	stream 
-		untilEnd: [self assertChunkIsWellFormed: stream nextChunk]
-		displayingProgress: 'Checking syntax...'
-!
-
-assertChunkIsWellFormed: chunk
-	self class parserClass new
-		parse: chunk readStream 
-		class: UndefinedObject 
-		noPattern: true
-		context: nil
-		notifying: nil
-		ifFail: [self assert: false]
-!
-
-assertContentsOf: strm match: expected 
-	| actual |
-	actual := strm contents.
-	self assert: actual size = expected size.
-	actual with: expected do: [:a :e | self assert: a = e]
-!
-
-assertMethodChunkIsWellFormed: chunk
-	self class parserClass new
-		parse: chunk readStream 
-		class: UndefinedObject 
-		noPattern: false
-		context: nil
-		notifying: nil
-		ifFail: [self assert: false]
-! !
-
-!MCStWriterTest methodsFor:'data'!
-
-expectedClassDefinitionA
- ^ '
-MCMock subclass: #MCMockClassA
-	instanceVariableNames: ''ivar''
-	classVariableNames: ''CVar''
-	poolDictionaries: ''''
-	category: ''Monticello-Mocks''!!
-
-!!MCMockClassA commentStamp: ''cwp 8/10/2003 16:43'' prior: 0!!
-This is a mock class. The Monticello tests manipulated it to simulate a developer modifying code in the image.!!
-'
-!
-
-expectedClassDefinitionB
- ^ '
-MCMock subclass: #MCMockClassB
-	instanceVariableNames: ''ivarb''
-	classVariableNames: ''CVar''
-	poolDictionaries: ''MCMockAPoolDictionary''
-	category: ''Monticello-Mocks''!!
-
-MCMockClassB class
-	instanceVariableNames: ''ciVar''!!
-
-!!MCMockClassB commentStamp: '''' prior: 0!!
-This comment has a bang!!!! Bang!!!! Bang!!!!!!
-'
-!
-
-expectedClassMethodDefinition
-	^ '
-!!MCMockClassA class methodsFor: ''as yet unclassified'' stamp: ''ab 7/7/2003 23:21''!!
-one
-
-	^ 1!! !!
-'
-!
-
-expectedMethodDefinition
-	^ '
-!!MCMockClassA methodsFor: ''numeric'' stamp: ''cwp 8/2/2003 17:26''!!
-one
-	^ 1!! !!
-'
-!
-
-expectedMethodDefinitionWithBangs
-	^ '
-!!MCStWriterTest methodsFor: ''testing'' stamp: ''cwp 8/9/2003 14:55''!!
-methodWithBangs
-	^ ''
-	^ ReadStream on: 
-''''MCRevisionInfo packageName: ''''MonticelloCompatibilityTest''''!!!!!!!!
-MCOrganizationDeclaration categories: 
-  #(
-  ''''Monticello-Mocks'''')!!!!!!!!
-
-MCClassDeclaration
-  name: #MCMockClassD
-  superclassName: #Object
-  category: #''''Monticello-Mocks''''
-  instVarNames: #()
-  comment: ''''''''!!!!!!!!
-
-MCMethodDeclaration className: #MCMockClassD selector: #one category: #''''as yet unclassified'''' timeStamp: ''''cwp 7/8/2003 21:21'''' source: 
-''''one
-	^ 1''''!!!!!!!!
-''''
-''
-!! !!
-'
-!
-
-expectedOrganizationDefinition
-	^ 'SystemOrganization addCategory: ''Monticello-Mocks''!!
-'
-! !
-
-!MCStWriterTest methodsFor:'testing'!
-
-expectedInitializerA
-	^ 'MCMockClassA initialize'
-!
-
-methodWithBangs
-	^ '
-	^ ReadStream on: 
-''MCRevisionInfo packageName: ''MonticelloCompatibilityTest''!!!!
-MCOrganizationDeclaration categories: 
-  #(
-  ''Monticello-Mocks'')!!!!
-
-MCClassDeclaration
-  name: #MCMockClassD
-  superclassName: #Object
-  category: #''Monticello-Mocks''
-  instVarNames: #()
-  comment: ''''!!!!
-
-MCMethodDeclaration className: #MCMockClassD selector: #one category: #''as yet unclassified'' timeStamp: ''cwp 7/8/2003 21:21'' source: 
-''one
-	^ 1''!!!!
-''
-'
-
-!
-
-setUp
-    stream := ReadWriteStream on:String new.
-    writer := MCStWriter on:stream.
-!
-
-testClassDefinitionA
-	writer visitClassDefinition: (self mockClassA asClassDefinition).
-	self assertContentsOf: stream match: self expectedClassDefinitionA.
-	stream reset.
-	2 timesRepeat: [self assertChunkIsWellFormed: stream nextChunk]
-!
-
-testClassDefinitionB
-	writer visitClassDefinition: (self mockClassB asClassDefinition).
-	self assertContentsOf: stream match: self expectedClassDefinitionB.
-	
-!
-
-testClassMethodDefinition
-	writer visitMethodDefinition: (MethodReference class: self mockClassA class selector: #one) 									asMethodDefinition.
-	self assertContentsOf: stream match: self expectedClassMethodDefinition.
-	stream reset.
-	self assert: stream nextChunk isAllSeparators.
-	self assertChunkIsWellFormed: stream nextChunk.
-	self assertMethodChunkIsWellFormed: stream nextChunk.
-	self assert: stream nextChunk isAllSeparators 
-!
-
-testInitializerDefinition
-	|chunk lastChunk|
-	writer writeSnapshot: self mockSnapshot.
-	stream reset.
-	[stream atEnd] whileFalse:
-		[chunk := stream nextChunk.
-		chunk isAllSeparators ifFalse: [lastChunk := chunk]].
-	self assertContentsOf: lastChunk readStream match: self expectedInitializerA
-!
-
-testMethodDefinition
-	writer visitMethodDefinition: (MethodReference class: self mockClassA selector: #one) 									asMethodDefinition.
-	self assertContentsOf: stream match: self expectedMethodDefinition.
-	stream reset.
-	self assert: stream nextChunk isAllSeparators.
-	self assertChunkIsWellFormed: stream nextChunk.
-	self assertMethodChunkIsWellFormed: stream nextChunk.
-	self assert: stream nextChunk isAllSeparators 
-!
-
-testMethodDefinitionWithBangs
-	writer visitMethodDefinition: (MethodReference 
-									class: self class 
-									selector: #methodWithBangs) asMethodDefinition.
-	self assertContentsOf: stream match: self expectedMethodDefinitionWithBangs.
-	stream reset.
-	self assert: stream nextChunk isAllSeparators.
-	self assertChunkIsWellFormed: stream nextChunk.
-	self assertMethodChunkIsWellFormed: stream nextChunk.
-	self assert: stream nextChunk isAllSeparators 
-!
-
-testOrganizationDefinition
-	| definition |
-	definition := MCOrganizationDefinition categories: 
-					(self mockPackage packageInfo systemCategories).
-	writer visitOrganizationDefinition: definition.
-	self assertContentsOf: stream match: self expectedOrganizationDefinition.
-	self assertAllChunksAreWellFormed.
-! !
-
-!MCStWriterTest class methodsFor:'documentation'!
-
-version
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCStWriterTest.st,v 1.1 2011-08-20 12:22:16 cg Exp $'
-!
-
-version_CVS
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCStWriterTest.st,v 1.1 2011-08-20 12:22:16 cg Exp $'
-!
-
-version_SVN
-    ^ '§Id: MCStWriterTest.st 7 2010-09-12 07:18:55Z vranyj1 §'
-! !
--- a/MCTestCase.st	Thu Apr 30 21:53:12 2015 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,230 +0,0 @@
-"{ Package: 'stx:goodies/monticello' }"
-
-TestCase subclass:#MCTestCase
-	instanceVariableNames:''
-	classVariableNames:''
-	poolDictionaries:''
-	category:'Monticello-Tests'
-!
-
-
-!MCTestCase class methodsFor:'as yet unclassified'!
-
-isAbstract
-	^ self = MCTestCase
-!
-
-resources
-	^ Array with: MCSnapshotResource
-! !
-
-!MCTestCase methodsFor:'asserting'!
-
-assertPackage: actual matches: expected
-	self assert: actual = expected
-
-!
-
-assertSnapshot: actual matches: expected
-	| diff |
-	diff := actual patchRelativeToBase: expected.
-	self assert: diff isEmpty
-
-!
-
-assertVersion: actual matches: expected
-	self assertPackage: actual package matches: expected package.	
-	self assertVersionInfo: actual info matches: expected info.
-	self assertSnapshot: actual snapshot matches: expected snapshot.
-!
-
-assertVersionInfo: actual matches: expected
-	self assert: actual name = expected name.
-	self assert: actual message = expected message.
-	self assert: actual ancestors size = expected ancestors size.
-	actual ancestors with: expected ancestors do: [:a :e | self assertVersionInfo: a matches: e]
-	
-! !
-
-!MCTestCase methodsFor:'compiling'!
-
-change: aSelector toReturn: anObject
-        self 
-                compileClass: self mockClassA 
-                source: aSelector, ' ^ ', anObject storeString 
-                category: 'numeric'
-
-    "Modified: / 13-09-2010 / 12:06:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-compileClass: aClass source: source category: category
-	aClass compileSilently: source classified: category
-!
-
-restoreMocks
-	self mockSnapshot updatePackage: self mockPackage
-! !
-
-!MCTestCase methodsFor:'mocks'!
-
-commentForClass: name
-	^ 'This is a comment for ', name
-!
-
-commentStampForClass: name
-	^ 'tester-', name,  ' 1/1/2000 00:00'
-!
-
-mockCategoryName
-	^ 'Monticello-Mocks'
-!
-
-mockClass: className super: superclassName
-	^ MCClassDefinition
-		name:  className
-		superclassName:  superclassName
-		category: self mockCategoryName
-		instVarNames: #()
-		classVarNames: #()
-		poolDictionaryNames: #()
-		classInstVarNames: #()
-		type: #normal
-		comment: (self commentForClass: className)
-		commentStamp: (self commentStampForClass: className)
-!
-
-mockClassA
-	^ Smalltalk at: #MCMockClassA
-!
-
-mockClassB
-	^ Smalltalk at: #MCMockClassB
-!
-
-mockDependencies
-	^ Array with: (MCVersionDependency package: self mockEmptyPackage info: (self mockVersionInfo: 'x'))
-!
-
-mockEmptyPackage
-	^ MCPackage named: (MCEmptyPackageInfo new packageName)
-!
-
-mockExtensionMethodCategory
-	^ MCMockPackageInfo new methodCategoryPrefix.
-!
-
-mockInstanceA
-	^ self mockClassA new
-!
-
-mockMessageString
-	^ 'A version generated for testing purposes.'
-!
-
-mockMethod: aSymbol class: className source: sourceString meta: aBoolean
-	^ MCMethodDefinition
-		className: className
-		classIsMeta: aBoolean
-		selector:  aSymbol
-		category: 'as yet unclassified'
-		timeStamp: ''
-		source: sourceString
-!
-
-mockOverrideMethodCategory
-	^ self mockExtensionMethodCategory, '-override'
-!
-
-mockPackage
-	^ MCSnapshotResource mockPackage
-!
-
-mockSnapshot
-	^ MCSnapshotResource current snapshot
-!
-
-mockToken: aSymbol
-	^ MCMockDefinition token: aSymbol
-!
-
-mockVersion
-	^ MCVersion 
-		package: self mockPackage
-		info: self mockVersionInfo
-		snapshot: self mockSnapshot
-!
-
-mockVersionInfo
-	^ self treeFrom: #(d ((b ((a))) (c)))
-!
-
-mockVersionInfo: tag 
-	^ MCVersionInfo
-		name: self mockVersionName, '-', tag asString
-		id: UUID new
-		message: self mockMessageString, '-', tag asString
-		date: Date today
-		time: Time now
-		author: Author initials
-		ancestors: #()
-
-!
-
-mockVersionInfoWithAncestor: aVersionInfo 
-	^ MCVersionInfo
-		name: aVersionInfo name, '-child'
-		id: UUID new
-		message: self mockMessageString
-		date: Date today
-		time: Time now
-		author: Author initials
-		ancestors: {aVersionInfo}
-
-!
-
-mockVersionName
-	^ 'MonticelloTest-xxx.1'
-!
-
-mockVersionWithAncestor: aMCVersion 
-	^ MCVersion
-		package: self mockPackage
-		info: (self mockVersionInfoWithAncestor: aMCVersion info)
-		snapshot: self mockSnapshot
-!
-
-mockVersionWithDependencies
-	^ MCVersion 
-		package: self mockPackage
-		info: self mockVersionInfo
-		snapshot: self mockSnapshot
-		dependencies: self mockDependencies
-!
-
-treeFrom: anArray
-	| name id |
-	name := anArray first.
-	id := '00000000-0000-0000-0000-0000000000', (name asString size = 1 ifTrue: [name asString, '0'] ifFalse: [name asString]).
-	^ MCVersionInfo
-		name: name
-		id: (UUID fromString: id)
-		message: ''
-		date: nil
-		time: nil
-		author: ''
-		ancestors: (anArray size > 1 ifTrue: [(anArray second collect: [:ea | self treeFrom: ea])] ifFalse: [#()])
-! !
-
-!MCTestCase class methodsFor:'documentation'!
-
-version
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCTestCase.st,v 1.2 2011-08-20 12:28:44 cg Exp $'
-!
-
-version_CVS
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCTestCase.st,v 1.2 2011-08-20 12:28:44 cg Exp $'
-!
-
-version_SVN
-    ^ '§Id: MCTestCase.st 10 2010-09-13 11:28:19Z vranyj1 §'
-! !
--- a/MCToolWindowBuilder.st	Thu Apr 30 21:53:12 2015 +0200
+++ b/MCToolWindowBuilder.st	Sun May 10 05:53:16 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/monticello' }"
 
+"{ NameSpace: Smalltalk }"
+
 Object subclass:#MCToolWindowBuilder
 	instanceVariableNames:'builder window currentFrame tool'
 	classVariableNames:''
@@ -142,3 +144,4 @@
 version
     ^ '$Header: /cvs/stx/stx/goodies/monticello/MCToolWindowBuilder.st,v 1.2 2012-09-11 21:14:34 cg Exp $'
 ! !
+
--- a/MCVersionTest.st	Thu Apr 30 21:53:12 2015 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,121 +0,0 @@
-"{ Package: 'stx:goodies/monticello' }"
-
-MCTestCase subclass:#MCVersionTest
-	instanceVariableNames:'version visited'
-	classVariableNames:''
-	poolDictionaries:''
-	category:'Monticello-Tests'
-!
-
-
-!MCVersionTest methodsFor:'asserting'!
-
-assert: aSelector orders: sexpr as: array
-	| expected |
-	expected := OrderedCollection new.
-	version := self versionFromTree: sexpr.
-	version perform: aSelector with: [:ea | expected add: ea info name].
-	self assert: expected asArray = array
-!
-
-assert: aSelector orders: sexpr as: expected unresolved: unresolved
-	| missing |
-	missing := OrderedCollection new.
-	version := self versionFromTree: sexpr.
-	version 
-		perform: aSelector 
-		with: [:ea | visited add: ea info name]
-		with: [:ea | missing add: ea name].
-	self assert: visited asArray = expected.
-	self assert: missing asArray = unresolved.
-! !
-
-!MCVersionTest methodsFor:'building'!
-
-dependencyFromTree: sexpr
-	^ MCMockDependency fromTree: sexpr
-!
-
-versionFromTree: sexpr
-	^ (self dependencyFromTree: sexpr) resolve
-! !
-
-!MCVersionTest methodsFor:'running'!
-
-setUp
-	visited := OrderedCollection new.
-! !
-
-!MCVersionTest methodsFor:'tests'!
-
-testAllAvailablePostOrder
-	self 
-		assert: #allAvailableDependenciesDo: 
-		orders: #(a ((b (d e)) c)) 
-		as: #(d e b c)
-!
-
-testAllMissing
-	self 
-		assert: #allDependenciesDo: 
-		orders: #(a ((b (d e)) (c missing))) 
-		as: #(d e b)
-!
-
-testAllUnresolved
-	self 
-		assert: #allDependenciesDo:ifUnresolved: 
-		orders: #(a ((b (d e)) (c missing)))
-		as: #(d e b)
-		unresolved: #(c)
-!
-
-testDependencyOrder
-	self 
-		assert: #allDependenciesDo: 
-		orders: #(a (b c)) 
-		as: #(b c)
-!
-
-testPostOrder
-	self 
-		assert: #allDependenciesDo: 
-		orders: #(a ((b (d e)) c)) 
-		as: #(d e b c)
-!
-
-testWithAll
-	self 
-		assert: #withAllDependenciesDo: 
-		orders: #(a ((b (d e)) c)) 
-		as: #(d e b c a)
-!
-
-testWithAllMissing
-	self 
-		assert: #withAllDependenciesDo: 
-		orders: #(a ((b (d e)) (c missing))) 
-		as: #(d e b a)
-!
-
-testWithAllUnresolved
-	self 
-		assert: #withAllDependenciesDo:ifUnresolved: 
-		orders: #(a ((b (d e)) (c missing)))
-		as: #(d e b a)
-		unresolved: #(c)
-! !
-
-!MCVersionTest class methodsFor:'documentation'!
-
-version
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCVersionTest.st,v 1.1 2011-08-20 12:26:03 cg Exp $'
-!
-
-version_CVS
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCVersionTest.st,v 1.1 2011-08-20 12:26:03 cg Exp $'
-!
-
-version_SVN
-    ^ '§Id: MCVersionTest.st 5 2010-08-29 07:30:29Z vranyj1 §'
-! !
--- a/MCWorkingCopyBrowser.st	Thu Apr 30 21:53:12 2015 +0200
+++ b/MCWorkingCopyBrowser.st	Sun May 10 05:53:16 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/monticello' }"
 
+"{ NameSpace: Smalltalk }"
+
 MCTool subclass:#MCWorkingCopyBrowser
 	instanceVariableNames:'workingCopy workingCopyWrapper repository defaults'
 	classVariableNames:''
@@ -538,4 +540,5 @@
     ^ '$Header: /cvs/stx/stx/goodies/monticello/MCWorkingCopyBrowser.st,v 1.2 2012-09-11 21:15:12 cg Exp $'
 ! !
 
+
 MCWorkingCopyBrowser initialize!
--- a/MCWorkingCopyTest.st	Thu Apr 30 21:53:12 2015 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,372 +0,0 @@
-"{ Package: 'stx:goodies/monticello' }"
-
-MCTestCase subclass:#MCWorkingCopyTest
-	instanceVariableNames:'savedInitials workingCopy repositoryGroup versions versions2'
-	classVariableNames:''
-	poolDictionaries:''
-	category:'Monticello-Tests'
-!
-
-
-!MCWorkingCopyTest methodsFor:'accessing'!
-
-description
-	^ self class name
-! !
-
-!MCWorkingCopyTest methodsFor:'actions'!
-
-basicMerge: aVersion
-	aVersion merge
-!
-
-load: aVersion
-	aVersion load
-!
-
-merge: aVersion
-	[[self basicMerge: aVersion]
-		on: MCMergeResolutionRequest do: [:n | n resume: true]]
-			on: MCNoChangesException do: [:n | ]
-!
-
-snapshot
-	| version |
-	[version := workingCopy newVersion]
-		on: MCVersionNameAndMessageRequest
-		do: [:n | n resume: (Array with: n suggestedName with: '')].
-	versions at: version info put: version.
-	^ version
-! !
-
-!MCWorkingCopyTest methodsFor:'asserting'!
-
-assertNameWhenSavingTo: aRepository is: aString
-	| name |
-	name := nil.
-	[aRepository storeVersion: workingCopy newVersion]
-		on: MCVersionNameAndMessageRequest
-		do: [:n | name := n suggestedName. n resume: (Array with: name with: '')].
-	self assert: name = aString
-!
-
-assertNumberWhenSavingTo: aRepository is: aNumber
-	| name |
-	name := nil.
-	[aRepository storeVersion: workingCopy newVersion]
-		on: MCVersionNameAndMessageRequest
-		do: [:n | name := n suggestedName. n resume: (Array with: name with: '')].
-	self assert: name = (self packageName, '-', Author initials, '.', aNumber asString)
-! !
-
-!MCWorkingCopyTest methodsFor:'private'!
-
-packageName
-	^ self mockPackage name
-! !
-
-!MCWorkingCopyTest methodsFor:'running'!
-
-clearPackageCache
-	| dir |
-	dir := MCCacheRepository default directory.
-	(dir fileNamesMatching: 'MonticelloMocks*') do: [:ea | dir deleteFileNamed: ea].
-	(dir fileNamesMatching: 'MonticelloTest*') do: [:ea | dir deleteFileNamed: ea].
-	(dir fileNamesMatching: 'rev*') do: [:ea | dir deleteFileNamed: ea].
-	(dir fileNamesMatching: 'foo-*') do: [:ea | dir deleteFileNamed: ea].
-	(dir fileNamesMatching: 'foo2-*') do: [:ea | dir deleteFileNamed: ea].
-!
-
-setUp
-        | repos1 repos2 |
-        self clearPackageCache.
-        repositoryGroup := MCRepositoryGroup new.
-        repositoryGroup disableCache.
-        workingCopy := MCWorkingCopy forPackage: self mockPackage.
-        versions := Dictionary new.
-        versions2 := Dictionary new.
-        repos1 := MCDictionaryRepository new dictionary: versions.
-        repos2 := MCDictionaryRepository new dictionary: versions2.
-        repositoryGroup addRepository: repos1.
-        repositoryGroup addRepository: repos2.
-        MCRepositoryGroup default removeRepository: repos1; removeRepository: repos2.
-        workingCopy repositoryGroup: repositoryGroup.
-        savedInitials := Author initials.
-        Author initials: 'abc'.
-
-    "Modified: / 13-09-2010 / 12:00:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-tearDown
-	workingCopy unregister.
-	self restoreMocks.
-	self clearPackageCache.
-	Author initials: savedInitials.
-! !
-
-!MCWorkingCopyTest methodsFor:'tests'!
-
-testAncestorMerge
-        | base revA revB revC |
-
-        base := self snapshot.
-        self change: #a toReturn: 'a1'.
-        revA :=  self snapshot.
-        self change: #b toReturn: 'b1'.
-        revB :=  self snapshot.         
-        self change: #c toReturn: 'c1'.
-        revC :=  self snapshot.
-
-        self should: [self basicMerge: revA] raise: MCNoChangesException.
-
-    "Modified: / 13-09-2010 / 12:18:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-testBackport
-	| inst base final backported |
-	inst := self mockInstanceA.
-	base :=  self snapshot.
-	self assert: inst one = 1.
-	self change: #one toReturn: 2.
-	self change: #two toReturn: 3.
-	final := self snapshot.
-	[workingCopy backportChangesTo: base info]
-		on: MCChangeSelectionRequest
-		do: [:e | e resume: e patch].
-	self assert: inst one = 2.
-	self assert: inst two = 3.
-	self assert: workingCopy ancestry ancestors size = 1.
-	self assert: workingCopy ancestry ancestors first = base info.
-	self assert: workingCopy ancestry stepChildren size = 1.
-	self assert: workingCopy ancestry stepChildren first = final info.
-	backported := self snapshot.
-	[workingCopy backportChangesTo: base info]
-		on: MCChangeSelectionRequest
-		do: [:e | e resume: e patch].
-	self assert: workingCopy ancestry ancestors size = 1.
-	self assert: workingCopy ancestry ancestors first = base info.
-	self assert: workingCopy ancestry stepChildren size = 1.
-	self assert: workingCopy ancestry stepChildren first = backported info.
-	
-!
-
-testDoubleRepeatedMerge
-	| base motherA1 motherA2 motherB1 motherB2 inst |
-
-	base := self snapshot.
-	self change: #a toReturn: 'a1'.
-	motherA1 :=  self snapshot.
-	self change: #c toReturn: 'c1'.
-	motherA2 :=  self snapshot.	
-	
-	self load: base.
-	self change: #b toReturn: 'b1'.
-	motherB1 :=  self snapshot.
-	self change: #d toReturn: 'd1'.
-	motherB2 :=  self snapshot.
-	
-	self load: base.
-	self merge: motherA1.
-	self merge: motherB1.
-	self change: #a toReturn: 'a2'.
-	self change: #b toReturn: 'b2'.
-	self snapshot.
-
-	self shouldnt: [self merge: motherA2] raise: Error.
-	self shouldnt: [self merge: motherB2] raise: Error.
-	
-	inst := self mockInstanceA.
-	self assert: inst a = 'a2'.
-	self assert: inst b = 'b2'.
-	self assert: inst c = 'c1'.
-	self assert: inst d = 'd1'.
-	
-!
-
-testMergeIntoImageWithNoChanges
-	| base revB revA1 |
-
-	self change: #a toReturn: 'a'.
-	base := self snapshot.
-	self change: #b toReturn: 'b'.
-	revB := self snapshot.
-	
-	self load: base.
-	self change: #a toReturn: 'a1'.
-	revA1 := self snapshot.
-
-	self change: #a toReturn: 'a'.
-	self snapshot.
-	self merge: revB.
-
-	self assert: (workingCopy ancestors size = 2)
-	
-!
-
-testMergeIntoUnmodifiedImage
-	| base revA |
-
-	base := self snapshot.
-	self change: #a toReturn: 'a1'.
-	revA := self snapshot.
-	
-	self load: base.
-
-	self merge: revA.
-
-	self assert: (workingCopy ancestors size = 1)
-	
-!
-
-testNaming
-	| repos version |
-
-	repos := MCDictionaryRepository new.
-	self assertNameWhenSavingTo: repos is: self packageName, '-abc.1'.
-	self assertNameWhenSavingTo: repos is: self packageName, '-abc.2'.
-	repos := MCDictionaryRepository new.
-	self assertNameWhenSavingTo: repos is: self packageName, '-abc.3'.
-	version := self snapshot.
-	version info instVarNamed: 'name' put: 'foo-jf.32'.
-	version load.
-	self assertNameWhenSavingTo: repos is: 'foo-abc.33'.
-	self assertNameWhenSavingTo: repos is: 'foo-abc.34'.
-	version info instVarNamed: 'name' put: 'foo-abc.35'.
-	repos storeVersion: version.
-	self assertNameWhenSavingTo: repos is: 'foo-abc.36'.
-	self assertNameWhenSavingTo: repos is: 'foo-abc.37'.
-	version info instVarNamed: 'name' put: 'foo-abc.10'.
-	repos storeVersion: version.
-	self assertNameWhenSavingTo: repos is: 'foo-abc.38'.
-	version info instVarNamed: 'name' put: 'foo2-ab.40'.
-	version load.
-	self assertNameWhenSavingTo: repos is: 'foo2-abc.41'.
-!
-
-testOptimizedLoad
-	| inst base diffy |
-	inst := self mockInstanceA.
-	base := self snapshot.
-	self change: #one toReturn: 2.
-	self assert: inst one = 2.
-	diffy := self snapshot asDiffAgainst: base.
-	self deny: diffy canOptimizeLoading.
-	self load: base.
-	self assert: inst one = 1.
-	self assert: diffy canOptimizeLoading.
-	self load: diffy.
-	self assert: inst one = 2.
-
-!
-
-testRedundantMerge
-	| base |
-	base :=  self snapshot.
-	self merge: base.
-	self shouldnt: [self merge: base] raise: Error.
-!
-
-testRepeatedMerge
-	| base mother1 mother2 inst |
-
-	base :=  self snapshot.
-	self change: #one toReturn: 2.
-	mother1 :=  self snapshot.
-	self change: #two toReturn: 3.
-	mother2 :=  self snapshot.	
-	
-	self load: base.
-	self change: #truth toReturn: false.
-	self snapshot.
-
-	inst := self mockInstanceA.
-	self assert: inst one = 1.
-	self assert: inst two = 2.	
-
-	self merge: mother1.
-	self assert: inst one = 2.
-	self assert: inst two = 2.	
-	
-	self change: #one toReturn: 7.
-	self assert: inst one = 7.
-	self assert: inst two = 2.
-	
-	self shouldnt: [self merge: mother2] raise: Error.
-	self assert: inst one = 7.
-	self assert: inst two = 3.
-!
-
-testRepositoryFallback
-	| version |
-	version := self snapshot.
-	self assert: (repositoryGroup versionWithInfo: version info) == version.
-	versions removeKey: version info.
-	versions2 at: version info put: version.
-	self assert: ( repositoryGroup versionWithInfo: version info) == version.
-	versions2 removeKey: version info.
-	self should: [repositoryGroup versionWithInfo: version info] raise: Error.
-!
-
-testSelectiveBackport
-	| inst base intermediate final patch selected |
-	inst := self mockInstanceA.
-	base :=  self snapshot.
-	self assert: inst one = 1.
-	self change: #one toReturn: 2.
-	intermediate := self snapshot.
-	self change: #two toReturn: 3.
-	final := self snapshot.
-	[workingCopy backportChangesTo: base info]
-		on: MCChangeSelectionRequest
-		do: [:e |
-			patch := e patch.
-			selected := patch operations select: [:ea | ea definition selector = #two].
-			e resume: (MCPatch operations: selected)]. 
-	self assert: inst one = 1.
-	self assert: inst two = 3.
-	self assert: workingCopy ancestry ancestors size = 1.
-	self assert: workingCopy ancestry ancestors first = base info.
-	self assert: workingCopy ancestry stepChildren size = 1.
-	self assert: workingCopy ancestry stepChildren first = final info
-!
-
-testSimpleMerge
-	| mother base inst |
-	inst := self mockInstanceA.
-	base :=  self snapshot.
-	self change: #one toReturn: 2.
-	mother :=  self snapshot.
-	self load: base.
-	self change: #two toReturn: 3.
-	self snapshot.
-	self assert: inst one = 1.
-	self assert: inst two = 3.
-	
-	self merge: mother.
-	self assert: inst one = 2.
-	self assert: inst two = 3.
-!
-
-testSnapshotAndLoad
-	| base inst |
-	inst := self mockInstanceA.
-	base :=  self snapshot.
-	self change: #one toReturn: 2.
-	self assert: inst one = 2.
-	self load: base.
-	self assert: inst one = 1.
-! !
-
-!MCWorkingCopyTest class methodsFor:'documentation'!
-
-version
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCWorkingCopyTest.st,v 1.1 2011-08-20 12:26:52 cg Exp $'
-!
-
-version_CVS
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCWorkingCopyTest.st,v 1.1 2011-08-20 12:26:52 cg Exp $'
-!
-
-version_SVN
-    ^ '§Id: MCWorkingCopyTest.st 10 2010-09-13 11:28:19Z vranyj1 §'
-! !
--- a/MCWorkingHistoryBrowser.st	Thu Apr 30 21:53:12 2015 +0200
+++ b/MCWorkingHistoryBrowser.st	Sun May 10 05:53:16 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/monticello' }"
 
+"{ NameSpace: Smalltalk }"
+
 MCVersionHistoryBrowser subclass:#MCWorkingHistoryBrowser
 	instanceVariableNames:''
 	classVariableNames:''
@@ -19,3 +21,4 @@
 version
     ^ '$Header: /cvs/stx/stx/goodies/monticello/MCWorkingHistoryBrowser.st,v 1.2 2012-09-11 21:14:18 cg Exp $'
 ! !
+
--- a/Make.proto	Thu Apr 30 21:53:12 2015 +0200
+++ b/Make.proto	Sun May 10 05:53:16 2015 +0100
@@ -157,7 +157,7 @@
 $(OUTDIR)MCNoChangesException.$(O) MCNoChangesException.$(H): MCNoChangesException.st $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)MCPackage.$(O) MCPackage.$(H): MCPackage.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)MCPackageCache.$(O) MCPackageCache.$(H): MCPackageCache.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)MCPackageEntry.$(O) MCPackageEntry.$(H): MCPackageEntry.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libwidg2/HierarchicalItem.$(H) $(STCHDR)
+$(OUTDIR)MCPackageEntry.$(O) MCPackageEntry.$(H): MCPackageEntry.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libwidg2/AbstractHierarchicalItem.$(H) $(INCLUDE_TOP)/stx/libwidg2/HierarchicalItem.$(H) $(STCHDR)
 $(OUTDIR)MCPackageLoader.$(O) MCPackageLoader.$(H): MCPackageLoader.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)MCPackageManager.$(O) MCPackageManager.$(H): MCPackageManager.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)MCPatch.$(O) MCPatch.$(H): MCPatch.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
@@ -166,7 +166,7 @@
 $(OUTDIR)MCReader.$(O) MCReader.$(H): MCReader.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)MCRepository.$(O) MCRepository.$(H): MCRepository.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)MCRepositoryBrowser.$(O) MCRepositoryBrowser.$(H): MCRepositoryBrowser.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libview2/ApplicationModel.$(H) $(INCLUDE_TOP)/stx/libview2/Model.$(H) $(STCHDR)
-$(OUTDIR)MCRepositoryEntry.$(O) MCRepositoryEntry.$(H): MCRepositoryEntry.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libwidg2/HierarchicalItem.$(H) $(STCHDR)
+$(OUTDIR)MCRepositoryEntry.$(O) MCRepositoryEntry.$(H): MCRepositoryEntry.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libwidg2/AbstractHierarchicalItem.$(H) $(INCLUDE_TOP)/stx/libwidg2/HierarchicalItem.$(H) $(STCHDR)
 $(OUTDIR)MCRepositoryGroup.$(O) MCRepositoryGroup.$(H): MCRepositoryGroup.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)MCScanner.$(O) MCScanner.$(H): MCScanner.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)MCSettingsApp.$(O) MCSettingsApp.$(H): MCSettingsApp.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libtool/AbstractSettingsApplication.$(H) $(INCLUDE_TOP)/stx/libview2/ApplicationModel.$(H) $(INCLUDE_TOP)/stx/libview2/Model.$(H) $(STCHDR)
@@ -182,7 +182,7 @@
 $(OUTDIR)MCVariableDefinition.$(O) MCVariableDefinition.$(H): MCVariableDefinition.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)MCVersion.$(O) MCVersion.$(H): MCVersion.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)MCVersionDependency.$(O) MCVersionDependency.$(H): MCVersionDependency.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)MCVersionEntry.$(O) MCVersionEntry.$(H): MCVersionEntry.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libwidg2/HierarchicalItem.$(H) $(STCHDR)
+$(OUTDIR)MCVersionEntry.$(O) MCVersionEntry.$(H): MCVersionEntry.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libwidg2/AbstractHierarchicalItem.$(H) $(INCLUDE_TOP)/stx/libwidg2/HierarchicalItem.$(H) $(STCHDR)
 $(OUTDIR)MCVersionLoader.$(O) MCVersionLoader.$(H): MCVersionLoader.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)MCVersionMerger.$(O) MCVersionMerger.$(H): MCVersionMerger.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)MCVersionNameAndMessageRequest.$(O) MCVersionNameAndMessageRequest.$(H): MCVersionNameAndMessageRequest.st $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Notification.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
--- a/bc.mak	Thu Apr 30 21:53:12 2015 +0200
+++ b/bc.mak	Sun May 10 05:53:16 2015 +0100
@@ -104,7 +104,7 @@
 $(OUTDIR)MCNoChangesException.$(O) MCNoChangesException.$(H): MCNoChangesException.st $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)MCPackage.$(O) MCPackage.$(H): MCPackage.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)MCPackageCache.$(O) MCPackageCache.$(H): MCPackageCache.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)MCPackageEntry.$(O) MCPackageEntry.$(H): MCPackageEntry.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libwidg2\HierarchicalItem.$(H) $(STCHDR)
+$(OUTDIR)MCPackageEntry.$(O) MCPackageEntry.$(H): MCPackageEntry.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libwidg2\AbstractHierarchicalItem.$(H) $(INCLUDE_TOP)\stx\libwidg2\HierarchicalItem.$(H) $(STCHDR)
 $(OUTDIR)MCPackageLoader.$(O) MCPackageLoader.$(H): MCPackageLoader.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)MCPackageManager.$(O) MCPackageManager.$(H): MCPackageManager.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)MCPatch.$(O) MCPatch.$(H): MCPatch.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
@@ -113,7 +113,7 @@
 $(OUTDIR)MCReader.$(O) MCReader.$(H): MCReader.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)MCRepository.$(O) MCRepository.$(H): MCRepository.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)MCRepositoryBrowser.$(O) MCRepositoryBrowser.$(H): MCRepositoryBrowser.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libview2\ApplicationModel.$(H) $(INCLUDE_TOP)\stx\libview2\Model.$(H) $(STCHDR)
-$(OUTDIR)MCRepositoryEntry.$(O) MCRepositoryEntry.$(H): MCRepositoryEntry.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libwidg2\HierarchicalItem.$(H) $(STCHDR)
+$(OUTDIR)MCRepositoryEntry.$(O) MCRepositoryEntry.$(H): MCRepositoryEntry.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libwidg2\AbstractHierarchicalItem.$(H) $(INCLUDE_TOP)\stx\libwidg2\HierarchicalItem.$(H) $(STCHDR)
 $(OUTDIR)MCRepositoryGroup.$(O) MCRepositoryGroup.$(H): MCRepositoryGroup.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)MCScanner.$(O) MCScanner.$(H): MCScanner.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)MCSettingsApp.$(O) MCSettingsApp.$(H): MCSettingsApp.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libtool\AbstractSettingsApplication.$(H) $(INCLUDE_TOP)\stx\libview2\ApplicationModel.$(H) $(INCLUDE_TOP)\stx\libview2\Model.$(H) $(STCHDR)
@@ -129,7 +129,7 @@
 $(OUTDIR)MCVariableDefinition.$(O) MCVariableDefinition.$(H): MCVariableDefinition.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)MCVersion.$(O) MCVersion.$(H): MCVersion.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)MCVersionDependency.$(O) MCVersionDependency.$(H): MCVersionDependency.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)MCVersionEntry.$(O) MCVersionEntry.$(H): MCVersionEntry.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libwidg2\HierarchicalItem.$(H) $(STCHDR)
+$(OUTDIR)MCVersionEntry.$(O) MCVersionEntry.$(H): MCVersionEntry.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libwidg2\AbstractHierarchicalItem.$(H) $(INCLUDE_TOP)\stx\libwidg2\HierarchicalItem.$(H) $(STCHDR)
 $(OUTDIR)MCVersionLoader.$(O) MCVersionLoader.$(H): MCVersionLoader.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)MCVersionMerger.$(O) MCVersionMerger.$(H): MCVersionMerger.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)MCVersionNameAndMessageRequest.$(O) MCVersionNameAndMessageRequest.$(H): MCVersionNameAndMessageRequest.st $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Notification.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
--- a/extensions.st	Thu Apr 30 21:53:12 2015 +0200
+++ b/extensions.st	Sun May 10 05:53:16 2015 +0100
@@ -473,7 +473,7 @@
 
 !stx_goodies_monticello class methodsFor:'documentation'!
 
-extensionsVersion_CVS
-    ^ '$Header: /cvs/stx/stx/goodies/monticello/extensions.st,v 1.27 2015-02-25 00:14:48 cg Exp $'
+extensionsVersion_HG
+
+    ^ '$Changeset: <not expanded> $'
 ! !
-
--- a/stx_goodies_monticello.st	Thu Apr 30 21:53:12 2015 +0200
+++ b/stx_goodies_monticello.st	Sun May 10 05:53:16 2015 +0100
@@ -305,5 +305,9 @@
 
 version_CVS
     ^ '$Header: /cvs/stx/stx/goodies/monticello/stx_goodies_monticello.st,v 1.25 2015-02-21 12:34:04 cg Exp $'
+!
+
+version_HG
+    ^ '$Changeset: <not expanded> $'
 ! !