Merge jv stx-8.0.0
authorHG Automerge
Thu, 24 Nov 2016 21:56:31 +0000
branchjv
changeset 1015 7b6393ea3d52
parent 1013 c8d5daf7e166 (diff)
parent 1014 8e77e7bafd66 (current diff)
child 1049 082a40c1cc3c
Merge
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/.hgignore	Thu Nov 24 21:56:31 2016 +0000
@@ -0,0 +1,16 @@
+
+syntax: glob
+*Init.c   
+makefile
+*.so
+*.H
+*.o
+*.STH
+*.sc
+objbc
+objvc
+*.class
+java/libs/*.jar
+java/libs-src/*.jar
+*-Test.xml
+st.chg
--- a/MCAncestry.st	Thu Nov 03 13:22:28 2016 +0100
+++ b/MCAncestry.st	Thu Nov 24 21:56:31 2016 +0000
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/monticello' }"
 
+"{ NameSpace: Smalltalk }"
+
 Object subclass:#MCAncestry
 	instanceVariableNames:'ancestors stepChildren'
 	classVariableNames:''
@@ -39,7 +41,9 @@
 !
 
 ancestors
-	^ ancestors ifNil: [#()]
+        ^ ancestors isNil ifTrue: [#()] ifFalse:[ancestors]
+
+    "Modified: / 07-09-2015 / 15:45:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 ancestorsDoWhileTrue: aBlock
@@ -148,3 +152,4 @@
 version
     ^ '$Header: /cvs/stx/stx/goodies/monticello/MCAncestry.st,v 1.2 2012-09-11 21:20:19 cg Exp $'
 ! !
+
--- a/MCAncestryTest.st	Thu Nov 03 13:22:28 2016 +0100
+++ /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 Nov 03 13:22:28 2016 +0100
+++ /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 Nov 03 13:22:28 2016 +0100
+++ /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 Nov 03 13:22:28 2016 +0100
+++ b/MCChangeSelector.st	Thu Nov 24 21:56:31 2016 +0000
@@ -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/MCClassDefinition.st	Thu Nov 03 13:22:28 2016 +0100
+++ b/MCClassDefinition.st	Thu Nov 24 21:56:31 2016 +0000
@@ -556,15 +556,27 @@
 !
 
 storeDataOn: aDataStream
-	| instVarSize |
-	instVarSize := (self hasTraitComposition or: [ self hasClassTraitComposition ])
-		ifTrue: [ self class instSize ]
-		ifFalse: [ self class instSize - 2 ].
-	aDataStream
-		beginInstance: self class
-		size: instVarSize.
-	1 to: instVarSize do: [ :index |
-		aDataStream nextPut: (self instVarAt: index) ].
+        | instVarSize |
+        instVarSize := (self hasTraitComposition or: [ self hasClassTraitComposition ])
+                ifTrue: [ self class instSize ]
+                ifFalse: [ self class instSize - 2 ].
+        aDataStream
+                beginInstance: self class
+                size: instVarSize.
+        1 to: instVarSize do: [ :index |
+                | value |
+
+                value := (self instVarAt: index).
+                "/ Special hack for ImmutableString / ImmutableArray which is not known by Squeak / Pharo,
+                "/ and therefore will fail to load properly there.
+                "/ In one of those is encountered, convert them to their mutable version.
+                (value class == ImmutableString or:[value class == ImmutableArray or:[value class == ImmutableByteArray]]) ifTrue:[ 
+                    value := value asMutableCollection.
+                ].
+                aDataStream nextPut: value 
+        ].
+
+    "Modified: / 23-04-2015 / 14:33:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !MCClassDefinition methodsFor:'testing'!
--- a/MCClassDefinitionTest.st	Thu Nov 03 13:22:28 2016 +0100
+++ /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/MCCommitDialog.st	Thu Nov 03 13:22:28 2016 +0100
+++ b/MCCommitDialog.st	Thu Nov 24 21:56:31 2016 +0000
@@ -34,12 +34,16 @@
 'A log message describing this version (your changes)'
 
 #includeExtrasForSTX
-'Include extra support files (makefiles) needed to build a binary class library under ST/X.
+'When checked, include extra support files (makefiles) needed to build a binary class library under ST/X.
 If this is not checked, only the plain code is saved which is needed to load the package as bytecode.
 Notice, that those files are not strictly required - they can easily be recreated by loading the package,
 and then recreating the support files from the system browser on the target system.
 Turn this off, if this package is meant to be transported to or shared with other Smalltalk dialects.
-(however, this is transparent to other Smalltalk dialects - these will simply ignore these additional definitions)'
+(however, this is transparent to other Smalltalk dialects - these will simply ignore these additional definitions)
+
+When unchecked, project definition class and version_XX methods are ommited (i.e., not present in .mcz).
+This may be desirable when commiting Smalltalk/X changes back to Squeak / Pharo upstream repository
+(and maintainer does not want these in the code even though it does not hurt)'
 
 #clearChangeSet
 'Clear the internal changeset after the Monticello commit'
@@ -51,6 +55,8 @@
 'The name of the version (will also be the name of the generated package file)'
 
 )
+
+    "Modified: / 24-04-2015 / 08:39:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !MCCommitDialog class methodsFor:'interface specs'!
@@ -214,7 +220,7 @@
         "/ sigh: make a new snapshot (now with updated version methods)
         version snapshot:version package snapshot.
         version cachable:false. "/ force new a write (otherwise, the mcz is not rewritten)
-        version snapshot includeExtrasForSTX:(DefaultForIncludeSTXExtras := self includeExtrasForSTX value).
+        version snapshot options includeExtrasForSTX:(DefaultForIncludeSTXExtras := self includeExtrasForSTX value).
         repository storeVersion: version.
 
         clearChangeSet ifTrue:[
@@ -225,6 +231,7 @@
 
     "Created: / 15-09-2010 / 14:07:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 24-07-2012 / 16:33:56 / cg"
+    "Modified: / 07-09-2015 / 15:27:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !MCCommitDialog methodsFor:'aspects'!
@@ -547,6 +554,11 @@
     ^ '$Header: /cvs/stx/stx/goodies/monticello/MCCommitDialog.st,v 1.13 2015-02-25 00:12:38 cg Exp $'
 !
 
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+!
+
 version_MC
     ^ '$stx:goodies/monticello-cg.3 4e70fe70-f030-11e1-ac62-001f3bda2d09 2012-08-27T12:16:46 cg$'
 !
--- a/MCDefinition.st	Thu Nov 03 13:22:28 2016 +0100
+++ b/MCDefinition.st	Thu Nov 24 21:56:31 2016 +0000
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/monticello' }"
 
+"{ NameSpace: Smalltalk }"
+
 Object subclass:#MCDefinition
 	instanceVariableNames:''
 	classVariableNames:'Instances'
@@ -150,6 +152,44 @@
 	self subclassResponsibility 
 ! !
 
+!MCDefinition methodsFor:'serializing'!
+
+storeDataOn: aDataStream
+    "Store myself on a DataStream.  
+     Answer self.  
+     This is a low-level DataStream/ReferenceStream method. 
+     See also objectToStoreOnDataStream.  
+     NOTE: This method must send 'aDataStream beginInstance:size:' and then (nextPut:/nextPutWeak:) its subobjects.  
+     readDataFrom:size: reads back what we write here."
+
+    | cntInstVars cntIndexedVars |
+
+    cntInstVars := self class instSize.
+    cntIndexedVars := self basicSize.
+    aDataStream
+        beginInstance: self class
+        size: cntInstVars + cntIndexedVars.
+    1 to: cntInstVars do:[:i | 
+        | value |
+
+        value := (self instVarAt: i).
+        "/ Special hack for ImmutableString / ImmutableArray which is not known by Squeak / Pharo,
+        "/ and therefore will fail to load properly there.
+        "/ In one of those is encountered, convert them to their mutable version.
+        (value class == ImmutableString or:[value class == ImmutableArray or:[value class == ImmutableByteArray]]) ifTrue:[ 
+            value := value asMutableCollection.
+        ].
+        aDataStream nextPut: value   
+    ].
+
+    "Write fields of a variable length object.  When writing to a dummy
+        stream, don't bother to write the bytes"
+    "1 to: cntInstVars do:
+        [:i | aDataStream nextPut: (self instVarAt: i)]."
+
+    "Created: / 23-04-2015 / 15:10:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
 !MCDefinition methodsFor:'testing'!
 
 isClassDefinition
@@ -185,6 +225,12 @@
     ^ '$Header: /cvs/stx/stx/goodies/monticello/MCDefinition.st,v 1.5 2012-09-11 21:21:09 cg Exp $'
 !
 
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+!
+
 version_SVN
     ^ '§Id: MCDefinition.st 24 2010-11-09 14:00:17Z vranyj1 §'
 ! !
+
--- a/MCDefinitionIndex.st	Thu Nov 03 13:22:28 2016 +0100
+++ b/MCDefinitionIndex.st	Thu Nov 24 21:56:31 2016 +0000
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/monticello' }"
 
+"{ NameSpace: Smalltalk }"
+
 Object subclass:#MCDefinitionIndex
 	instanceVariableNames:'definitions'
 	classVariableNames:''
@@ -68,6 +70,11 @@
     ^ '$Header: /cvs/stx/stx/goodies/monticello/MCDefinitionIndex.st,v 1.5 2013-05-15 11:57:02 cg Exp $'
 !
 
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+!
+
 version_SVN
     ^ '$Id: MCDefinitionIndex.st,v 1.5 2013-05-15 11:57:02 cg Exp $'
 ! !
--- a/MCDependencySorterTest.st	Thu Nov 03 13:22:28 2016 +0100
+++ /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 Nov 03 13:22:28 2016 +0100
+++ b/MCDependentsWrapper.st	Thu Nov 24 21:56:31 2016 +0000
@@ -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/MCDialog.st	Thu Nov 03 13:22:28 2016 +0100
+++ b/MCDialog.st	Thu Nov 24 21:56:31 2016 +0000
@@ -25,6 +25,8 @@
 "
 "{ Package: 'stx:goodies/monticello' }"
 
+"{ NameSpace: Smalltalk }"
+
 SimpleDialog subclass:#MCDialog
 	instanceVariableNames:'onCancelBlock onAcceptBlock modelHolder titleHolder
 		subtitleHolder infoHolder progressIndicator worker exception'
@@ -154,54 +156,55 @@
     <resource: #canvas>
 
     ^ 
-     #(FullSpec
-        name: buttonsSpec
-        window: 
-       (WindowSpec
-          label: 'Buttons'
-          name: 'Buttons'
-          min: (Point 10 10)
-          bounds: (Rectangle 0 0 400 30)
-        )
-        component: 
-       (SpecCollection
-          collection: (
-           (HorizontalPanelViewSpec
-              name: 'ButtonPanel'
-              layout: (LayoutFrame 0 0 0 0 0 1 0 1)
-              horizontalLayout: rightSpace
-              verticalLayout: center
-              horizontalSpace: 3
-              verticalSpace: 3
-              component: 
-             (SpecCollection
-                collection: (
-                 (ActionButtonSpec
-                    label: 'OK'
-                    name: 'AcceptButton'
-                    translateLabel: true
-                    labelChannel: acceptButtonTitleAspect
-                    model: doAccept
-                    enableChannel: acceptEnabledHolder
-                    isDefault: true
-                    defaultable: true
-                    extent: (Point 125 22)
-                  )
-                 (ActionButtonSpec
-                    label: 'Cancel'
-                    name: 'CancelButton'
-                    translateLabel: true
-                    model: doCancel
-                    extent: (Point 125 22)
-                  )
+    #(FullSpec
+       name: buttonsSpec
+       window: 
+      (WindowSpec
+         label: 'Buttons'
+         name: 'Buttons'
+         min: (Point 10 10)
+         bounds: (Rectangle 0 0 400 30)
+       )
+       component: 
+      (SpecCollection
+         collection: (
+          (HorizontalPanelViewSpec
+             name: 'ButtonPanel'
+             layout: (LayoutFrame 0 0 0 0 0 1 0 1)
+             horizontalLayout: okCancelBox
+             verticalLayout: center
+             horizontalSpace: 3
+             verticalSpace: 3
+             reverseOrderIfOKAtLeft: true
+             component: 
+            (SpecCollection
+               collection: (
+                (ActionButtonSpec
+                   label: 'Cancel'
+                   name: 'CancelButton'
+                   translateLabel: true
+                   model: doCancel
+                   extent: (Point 195 22)
                  )
-               
-              )
-            )
+                (ActionButtonSpec
+                   label: 'OK'
+                   name: 'AcceptButton'
+                   translateLabel: true
+                   labelChannel: acceptButtonTitleAspect
+                   model: doAccept
+                   enableChannel: acceptEnabledHolder
+                   isDefault: true
+                   defaultable: true
+                   extent: (Point 196 22)
+                 )
+                )
+              
+             )
            )
-         
-        )
-      )
+          )
+        
+       )
+     )
 !
 
 contentSpec
@@ -408,97 +411,99 @@
     <resource: #canvas>
 
     ^ 
-     #(FullSpec
-        name: windowSpec
-        window: 
-       (WindowSpec
-          label: 'SubVersion: Commit '
-          name: 'SubVersion: Commit '
-          labelChannel: titleHolder
-          min: (Point 10 10)
-          bounds: (Rectangle 0 0 648 451)
-        )
-        component: 
-       (SpecCollection
-          collection: (
-           (ViewSpec
-              name: 'TitleBox'
-              layout: (LayoutFrame 0 0 0 0 0 1 66 0)
-              backgroundColor: (Color 100.0 100.0 100.0)
-              component: 
-             (SpecCollection
-                collection: (
-                 (LabelSpec
-                    label: 'SVN Dialog'
-                    name: 'DialogTitle'
-                    layout: (LayoutFrame 10 0 0 0 -75 1 40 0)
-                    style: (FontDescription helvetica medium roman 18 #'iso10646-1')
-                    backgroundColor: (Color 100.0 100.0 100.0)
-                    translateLabel: true
-                    labelChannel: titleHolder
-                    adjust: left
-                  )
-                 (LabelSpec
-                    label: 'SVN Dialog Subtitle'
-                    name: 'DialogSubtitle'
-                    layout: (LayoutFrame 30 0 40 0 -75 1 66 0)
-                    backgroundColor: (Color 100.0 100.0 100.0)
-                    translateLabel: true
-                    labelChannel: subtitleHolder
-                    resizeForLabel: false
-                    adjust: left
-                  )
-                 (LabelSpec
-                    label: 'Icon'
-                    name: 'DialogIcon'
-                    layout: (LayoutFrame -75 1 0 0 0 1 66 0)
-                    hasCharacterOrientedLabel: false
-                    backgroundColor: (Color 100.0 100.0 100.0)
-                    translateLabel: true
-                    labelChannel: dialogIconAspect
-                  )
+    #(FullSpec
+       name: windowSpec
+       window: 
+      (WindowSpec
+         label: 'SubVersion: Commit '
+         name: 'SubVersion: Commit '
+         labelChannel: titleHolder
+         min: (Point 10 10)
+         bounds: (Rectangle 0 0 648 451)
+       )
+       component: 
+      (SpecCollection
+         collection: (
+          (ViewSpec
+             name: 'TitleBox'
+             layout: (LayoutFrame 0 0 0 0 0 1 66 0)
+             backgroundColor: (Color 100.0 100.0 100.0)
+             component: 
+            (SpecCollection
+               collection: (
+                (LabelSpec
+                   label: 'SVN Dialog'
+                   name: 'DialogTitle'
+                   layout: (LayoutFrame 10 0 0 0 -75 1 40 0)
+                   style: (FontDescription helvetica medium roman 18 #'iso10646-1')
+                   backgroundColor: (Color 100.0 100.0 100.0)
+                   translateLabel: true
+                   labelChannel: titleHolder
+                   adjust: left
+                 )
+                (LabelSpec
+                   label: 'SVN Dialog Subtitle'
+                   name: 'DialogSubtitle'
+                   layout: (LayoutFrame 30 0 40 0 -75 1 66 0)
+                   backgroundColor: (Color 100.0 100.0 100.0)
+                   translateLabel: true
+                   labelChannel: subtitleHolder
+                   resizeForLabel: false
+                   adjust: left
                  )
-               
-              )
-            )
-           (SubCanvasSpec
-              name: 'Content'
-              layout: (LayoutFrame 5 0 70 0 -5 1 -50 1)
-              hasHorizontalScrollBar: false
-              hasVerticalScrollBar: false
-              specHolder: contentSpecHolder
-              createNewBuilder: false
-            )
-           (DividerSpec
-              name: 'Separator'
-              layout: (LayoutFrame 5 0 -50 1 -5 1 -30 1)
-            )
-           (UISubSpecification
-              name: 'Buttons'
-              layout: (LayoutFrame 130 0 -30 1 0 1 0 1)
-              minorKey: buttonsSpec
-              keepSpaceForOSXResizeHandleH: true
-            )
-           (LinkButtonSpec
-              label: 'Help'
-              name: 'Help'
-              layout: (LayoutFrame 53 0 -26 1 153 0 -3 1)
-              visibilityChannel: false
-              foregroundColor: (Color 0.0 0.0 86.9993133440147)
-              translateLabel: true
-              model: doHelp
-            )
-           (MenuPanelSpec
-              name: 'More'
-              layout: (LayoutFrame 0 0 -30 1 62 0 0 1)
-              level: 0
-              model: doInspect
-              menu: actionsMenu
-            )
+                (LabelSpec
+                   label: 'Icon'
+                   name: 'DialogIcon'
+                   layout: (LayoutFrame -75 1 0 0 0 1 66 0)
+                   hasCharacterOrientedLabel: false
+                   backgroundColor: (Color 100.0 100.0 100.0)
+                   translateLabel: true
+                   labelChannel: dialogIconAspect
+                 )
+                )
+              
+             )
+           )
+          (SubCanvasSpec
+             name: 'Content'
+             layout: (LayoutFrame 5 0 70 0 -5 1 -50 1)
+             hasHorizontalScrollBar: false
+             hasVerticalScrollBar: false
+             specHolder: contentSpecHolder
+             createNewBuilder: false
+           )
+          (DividerSpec
+             name: 'Separator'
+             layout: (LayoutFrame 5 0 -50 1 -5 1 -30 1)
            )
-         
-        )
-      )
+          (LinkButtonSpec
+             label: 'Help'
+             name: 'Help'
+             layout: (LayoutFrame 53 0 -26 1 153 0 -3 1)
+             initiallyInvisible: true
+             visibilityChannel: false
+             foregroundColor: (Color 0.0 0.0 87.0)
+             translateLabel: true
+             model: doHelp
+           )
+          (MenuPanelSpec
+             name: 'More'
+             layout: (LayoutFrame 0 0 -30 1 62 0 0 1)
+             level: 0
+             visibilityChannel: false
+             model: doInspect
+             menu: actionsMenu
+           )
+          (UISubSpecification
+             name: 'Buttons'
+             layout: (LayoutFrame 0 0 -30 1 0 1 0 1)
+             minorKey: buttonsSpec
+             keepSpaceForOSXResizeHandleH: true
+           )
+          )
+        
+       )
+     )
 ! !
 
 !MCDialog class methodsFor:'menu specs'!
@@ -986,6 +991,11 @@
     ^ '$Header: /cvs/stx/stx/goodies/monticello/MCDialog.st,v 1.6 2013-03-28 00:13:45 cg Exp $'
 !
 
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+!
+
 version_SVN
     ^ '§Id: MCDialog.st 12 2010-09-15 13:13:22Z vranyj1 §'
 ! !
--- a/MCDictionaryRepositoryTest.st	Thu Nov 03 13:22:28 2016 +0100
+++ /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 Nov 03 13:22:28 2016 +0100
+++ /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 Nov 03 13:22:28 2016 +0100
+++ /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 Nov 03 13:22:28 2016 +0100
+++ b/MCFileRepositoryInspector.st	Thu Nov 24 21:56:31 2016 +0000
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/monticello' }"
 
+"{ NameSpace: Smalltalk }"
+
 MCVersionInspector subclass:#MCFileRepositoryInspector
 	instanceVariableNames:'repository versions loaded newer inherited selectedPackage
 		selectedVersion order versionInfo'
--- a/MCHttpRepository.st	Thu Nov 03 13:22:28 2016 +0100
+++ b/MCHttpRepository.st	Thu Nov 24 21:56:31 2016 +0000
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/monticello' }"
 
+"{ NameSpace: Smalltalk }"
+
 MCFileBasedRepository subclass:#MCHttpRepository
 	instanceVariableNames:'location user password readerCache'
 	classVariableNames:''
@@ -218,18 +220,27 @@
 !
 
 writeStreamForFileNamed: aString replace: ignoreBoolean do: aBlock
-	| stream response |
-	stream := RWBinaryOrTextStream on: String new.
-	aBlock value: stream.
-	response := HTTPSocket
-					httpPut: stream contents
-					to: (self urlForFileNamed: aString)
-					user: self user
-					passwd: self password.
+        | stream response |
+        stream := RWBinaryOrTextStream on: String new.
+        aBlock value: stream.
+"/        response := HTTPSocket
+"/                                        httpPut: stream contents
+"/                                        to: (self urlForFileNamed: aString)
+"/                                        user: self user
+"/                                        passwd: self password.
+        response := HTTPInterface
+                        request:#PUT
+                        url:(self urlForFileNamed: aString)
+                        fromHost:nil port:nil
+                        accept:#('*/*')
+                        fromDocument:nil
+                        userName:self user password: self password 
+                        contentType:'application/octet-stream'
+                        contents:stream contents asString.
 
-	(#( 'HTTP/1.1 201 ' 'HTTP/1.1 200 ' 'HTTP/1.0 201 ' 'HTTP/1.0 200 ')
-		anySatisfy: [:code | response beginsWith: code ])
-			ifFalse: [self error: response].
+        (#( 201 200 ) includes: response responseCode) ifFalse: [self error: response].
+
+    "Modified: / 24-04-2015 / 00:12:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !MCHttpRepository class methodsFor:'documentation'!
@@ -242,6 +253,11 @@
     ^ '$Header: /cvs/stx/stx/goodies/monticello/MCHttpRepository.st,v 1.7 2014-02-12 14:53:40 cg Exp $'
 !
 
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+!
+
 version_SVN
     ^ '$Id: MCHttpRepository.st,v 1.7 2014-02-12 14:53:40 cg Exp $'
 ! !
--- a/MCInitializationTest.st	Thu Nov 03 13:22:28 2016 +0100
+++ /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/MCLazyVersionInfo.st	Thu Nov 03 13:22:28 2016 +0100
+++ b/MCLazyVersionInfo.st	Thu Nov 24 21:56:31 2016 +0000
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/monticello' }"
 
+"{ NameSpace: Smalltalk }"
+
 MCVersionInfo subclass:#MCLazyVersionInfo
 	instanceVariableNames:'ancestorsProps stepChildrenProps'
 	classVariableNames:''
@@ -21,13 +23,14 @@
 
 ancestors
 
-    ancestors ifNil:
-        [ancestorsProps ifNotNil:
+    ancestors isNil ifTrue:
+        [ancestorsProps notNil ifTrue:
             [ancestors := ancestorsProps collect:[:p|MCLazyVersionInfo withProperties:p].
             ancestorsProps := nil]].
     ^super ancestors
 
     "Created: / 28-10-2010 / 17:51:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 07-09-2015 / 15:45:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 stepChildren
@@ -52,11 +55,14 @@
     time:= ([ Time fromString:(dict at: #time)] on: Error do: [ :ex | ex return: nil ]).
     author:= (dict at: #author ifAbsent: ['']).
 
-    ancestorsProps:= dict at: #ancestors ifAbsent:[#()].
+    (dict includesKey: #ancestors) ifTrue:[ 
+        ancestorsProps:= dict at: #ancestors.
+        ancestors := nil.
+    ].
     stepChildrenProps:= dict at: #stepChildren ifAbsent: [#()].
 
     "Created: / 28-10-2010 / 15:36:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 28-10-2010 / 17:49:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 12-05-2015 / 01:05:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !MCLazyVersionInfo class methodsFor:'documentation'!
@@ -69,6 +75,12 @@
     ^ '$Header: /cvs/stx/stx/goodies/monticello/MCLazyVersionInfo.st,v 1.3 2012-09-11 21:22:41 cg Exp $'
 !
 
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+!
+
 version_SVN
     ^ '§Id: MCLazyVersionInfo.st 23 2010-10-29 14:41:24Z vranyj1 §'
 ! !
+
--- a/MCMczInstallerTest.st	Thu Nov 03 13:22:28 2016 +0100
+++ /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/MCMczReader.st	Thu Nov 03 13:22:28 2016 +0100
+++ b/MCMczReader.st	Thu Nov 24 21:56:31 2016 +0000
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/monticello' }"
 
+"{ NameSpace: Smalltalk }"
+
 MCVersionReader subclass:#MCMczReader
 	instanceVariableNames:'zip infoCache'
 	classVariableNames:''
@@ -16,6 +18,16 @@
 
 !MCMczReader class methodsFor:'testing'!
 
+canReadFileNamed: fileName
+    "Hack to use MCStXMczReader on Smalltalk/X"
+
+    ^ ((Smalltalk respondsTo: #isSmalltalkX) and:[ Smalltalk isSmalltalkX ]) 
+        ifTrue:[ self == MCStXMczReader and: [ super canReadFileNamed: fileName ] ]
+        ifFalse:[ super canReadFileNamed: fileName ].
+
+    "Created: / 10-05-2015 / 06:05:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 supportsDependencies
 	^ true
 !
--- a/MCMergeBrowser.st	Thu Nov 03 13:22:28 2016 +0100
+++ b/MCMergeBrowser.st	Thu Nov 24 21:56:31 2016 +0000
@@ -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 Nov 03 13:22:28 2016 +0100
+++ /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 Nov 03 13:22:28 2016 +0100
+++ /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 Nov 03 13:22:28 2016 +0100
+++ /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 Nov 03 13:22:28 2016 +0100
+++ /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 Nov 03 13:22:28 2016 +0100
+++ /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 Nov 03 13:22:28 2016 +0100
+++ /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 Nov 03 13:22:28 2016 +0100
+++ /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 Nov 03 13:22:28 2016 +0100
+++ /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 Nov 03 13:22:28 2016 +0100
+++ /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 Nov 03 13:22:28 2016 +0100
+++ /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 Nov 03 13:22:28 2016 +0100
+++ /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 Nov 03 13:22:28 2016 +0100
+++ /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 Nov 03 13:22:28 2016 +0100
+++ /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 Nov 03 13:22:28 2016 +0100
+++ /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/MCRepositoryBrowser.st	Thu Nov 03 13:22:28 2016 +0100
+++ b/MCRepositoryBrowser.st	Thu Nov 24 21:56:31 2016 +0000
@@ -594,17 +594,32 @@
             label: '-'
           )
          (MenuItem
-            label: 'Compare with Image'
+            label: 'Compare'
             itemValue: versionCompareWithImage
           )
          (MenuItem
             label: '-'
           )
          (MenuItem
+            label: 'Update Code...'
+            itemValue: versionUpdateCode
+          )
+         (MenuItem
+            enabled: canUpdateSplicemap
+            label: 'Update Splicemap...'
+            itemValue: versionUpdateSplicemap
+          )
+         (MenuItem
+            label: '-'
+          )
+         (MenuItem
             label: 'Save .mcz File As...'
             itemValue: saveMCZFileAs
           )
          (MenuItem
+            label: '-'
+          )
+         (MenuItem
             label: 'Show in File Browser'
             itemValue: showPackageInFileBrowser
           )
@@ -729,6 +744,12 @@
 
 !MCRepositoryBrowser methodsFor:'aspect-queries'!
 
+canUpdateSplicemap
+    ^ ConfigurableFeatures hasMercurialSupport
+
+    "Created: / 08-09-2015 / 00:56:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 hasRepositorySelectedHolder
     ^ BlockValue
         with:[:h | h value notNil]
@@ -1211,23 +1232,62 @@
 
 versionCompareWithImage
 
-    | version snapshot |
+    | version package |
+
+    self withWaitCursorDo:[
+        version := self selectedVersionAsMCVersion.
+        version isNil ifTrue:[ ^ self ].
+        package := Dialog requestProject:(resources string: 'Package to compare with') initialAnswer:package suggestions: nil.
+        package isNil ifTrue:[ ^ self ].
+        self versionCompareWithImagePackage: package.  
+    ].
+
+    "Modified: / 02-10-2015 / 16:27:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+versionCompareWithImagePackage: package
+
+    | version snapshot snapshotCS packageCS diffset diffCS |
 
     self withWaitCursorDo:[
         version := self selectedVersionAsMCVersion.
         version isNil ifTrue:[ ^ self ].
         snapshot := version snapshot.
-        (Tools::ChangeSetBrowser2 
-                on: (snapshot asChangeSet name:('Diff for: ',version fileName))
-                label: version info name)
+        snapshotCS := snapshot asChangeSet.
+        snapshotCS name: version info name.     
+        packageCS := ChangeSet forPackage: package.
+        "/ Remove St/X specific method and classes (used for package management)
+        packageCS := packageCS reject:[:chg |  
+            chg changeClass theNonMetaclass isProjectDefinition or:[ chg isMethodDefinitionChange and:[ AbstractSourceCodeManager isVersionMethodSelector: chg selector ]]
+        ].
+        diffset := snapshotCS diffSetsAgainst: packageCS.  
+        diffCS := ChangeSet new.
+        diffCS addAll: (diffset onlyInReceiver).
+        diffCS addAll: (diffset changed collect:[:pair | pair first ]).
+        diffCS addAll: (diffset onlyInArg collect:[ :chg | chg asAntiChange ]).
+        "/ Filter out Organization change - not needed for Smalltalk/X
+        (diffCS first isOtherChange and:[ diffCS first source startsWith: '" Organization:' ]) ifTrue:[ 
+            diffCS removeFirst.
+        ].
+        "/ Sort so that class definitions are first and
+        "/ class removals last.
+        diffCS sort:[ :a :b | (a isClassDefinitionChange and:[b isClassDefinitionChange not]) or:[ a isClassRemoveChange not  and:[ b isClassRemoveChange ] ] ].
+        "/ Set the package so when applied, the change goes to the 
+        "/ correct package (if not overriden by 'target package'.
+        diffCS do:[:each | each package: package ].
+
+        diffCS name: (resources string: 'Diffs between %1 (MC version) and %2 (in image)' with: version info name with: package).
+        (Tools::ChangeSetBrowser2 on: diffCS)
             beOneColumn;
             showSame: false;
             targetNamespace:targetNamespace;
             targetPackage:targetPackage;
-            open
+            allowRemove: true;        
+            open       
     ].
 
-    "Modified: / 01-11-2014 / 00:04:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Created: / 07-09-2015 / 18:41:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 02-10-2015 / 16:27:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 versionInspect
@@ -1320,6 +1380,68 @@
 
     "Modified: / 09-11-2010 / 13:33:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 07-09-2011 / 12:47:51 / cg"
+!
+
+versionUpdateCode
+
+    | version package snapshot snapshotCS |
+
+    self withWaitCursorDo:[
+        version := self selectedVersionAsMCVersion.
+        version isNil ifTrue:[ ^ self ].
+        snapshot := version snapshot.
+        snapshotCS := snapshot asChangeSet.
+        snapshotCS name: version info name.
+        ProjectDefinition allSubclassesDo:[ :def |
+            ((def class compiledMethodAt: #monticelloName) notNil and:[
+                def monticelloName = version package name]) ifTrue:[ 
+                package := def package.
+            ].
+        ].
+        package isNil ifTrue:[ 
+            Dialog warn: (resources string: 'No package found for Monticello package ''%1''' with: version package name).
+            ^ self
+        ].
+        self versionCompareWithImagePackage: package.  
+    ].
+
+    "Created: / 07-09-2015 / 18:36:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+versionUpdateSplicemap
+
+    | version package dialog revset packageDef splicemap |
+
+    self withWaitCursorDo:[
+        version := self selectedVersionAsMCVersion.
+        version isNil ifTrue:[ ^ self ].
+        ProjectDefinition allSubclassesDo:[ :def |
+            ((def class compiledMethodAt: #monticelloName) notNil and:[
+                def monticelloName = version package name]) ifTrue:[ 
+                package := def package.
+                packageDef := def.
+            ].
+        ].
+        package isNil ifTrue:[ 
+            Dialog warn: (resources string: 'No package found for Monticello package ''%1''' with: version package name).
+            ^ self
+        ].
+        revset := 'grep(''%1'')' bindWith: version info name.
+
+        dialog := HGChangesetDialog new.
+        dialog repository: (HGPackageWorkingCopy named:package) repository .
+        dialog revset: revset asHGRevset.
+        dialog open ifFalse:[ ^ self ].
+        splicemap := { dialog changeset id literalArrayEncoding . version info literalArrayEncodingWithoutAncestors } 
+                        , packageDef monticelloSplicemap.
+        packageDef theMetaclass 
+                compile: (packageDef monticelloSplicemap_codeFor:splicemap)
+                classified:(packageDef class lookupMethodFor: #monticelloSplicemap) category
+
+    ].
+
+    "Created: / 07-09-2015 / 18:37:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 08-09-2015 / 00:07:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !MCRepositoryBrowser methodsFor:'updating'!
@@ -1366,6 +1488,11 @@
     ^ '$Header: /cvs/stx/stx/goodies/monticello/MCRepositoryBrowser.st,v 1.38 2015-02-09 13:57:08 cg Exp $'
 !
 
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+!
+
 version_SVN
     ^ '$Id: MCRepositoryBrowser.st,v 1.38 2015-02-09 13:57:08 cg Exp $'
 ! !
--- a/MCRepositoryDialog.st	Thu Nov 03 13:22:28 2016 +0100
+++ b/MCRepositoryDialog.st	Thu Nov 24 21:56:31 2016 +0000
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/monticello' }"
 
+"{ NameSpace: Smalltalk }"
+
 MCDialog subclass:#MCRepositoryDialog
 	instanceVariableNames:'repositoryTypeHolder'
 	classVariableNames:''
@@ -110,6 +112,12 @@
     ^ '$Header: /cvs/stx/stx/goodies/monticello/MCRepositoryDialog.st,v 1.2 2012-09-11 21:13:56 cg Exp $'
 !
 
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+!
+
 version_SVN
     ^ '§Id: MCRepositoryDialog.st 19 2010-10-14 10:51:48Z vranyj1 §'
 ! !
+
--- a/MCRepositoryInspector.st	Thu Nov 03 13:22:28 2016 +0100
+++ b/MCRepositoryInspector.st	Thu Nov 24 21:56:31 2016 +0000
@@ -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 Nov 03 13:22:28 2016 +0100
+++ /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 Nov 03 13:22:28 2016 +0100
+++ b/MCSMCacheRepository.st	Thu Nov 24 21:56:31 2016 +0000
@@ -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 Nov 03 13:22:28 2016 +0100
+++ b/MCSaveVersionDialog.st	Thu Nov 24 21:56:31 2016 +0000
@@ -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 Nov 03 13:22:28 2016 +0100
+++ /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 Nov 03 13:22:28 2016 +0100
+++ /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/MCSnapshot.st	Thu Nov 03 13:22:28 2016 +0100
+++ b/MCSnapshot.st	Thu Nov 24 21:56:31 2016 +0000
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/monticello' }"
 
+"{ NameSpace: Smalltalk }"
+
 Object subclass:#MCSnapshot
 	instanceVariableNames:'definitions'
 	classVariableNames:''
@@ -33,19 +35,42 @@
 !
 
 includeExtrasForSTX
-    "/ do not default to true here, as the version is snapshotted twice in order to
-    "/ update the version-strings, and we don not need this stuff in the first round!!
-    | includeExtrasForSTX |
-    includeExtrasForSTX := self objectAttributeAt: #includeExtrasForSTX.
-    ^ includeExtrasForSTX ? false
+   <resource: #obsolete>
+
+   self obsoleteFeatureWarning:'Use `options includeExtrasForSTX` instead'.
+   ^ self options includeExtrasForSTX
+
+    "Modified: / 07-09-2015 / 15:28:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
 
-    "Modified: / 12-08-2013 / 01:57:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+includeExtrasForSTX: aBoolean
+   <resource: #obsolete>
+
+   self obsoleteFeatureWarning:'Use `options includeExtrasForSTX: aBoolean` instead'.
+   self options includeExtrasForSTX: aBoolean
+
+    "Modified: / 07-09-2015 / 15:27:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
-includeExtrasForSTX:something
-    self objectAttributeAt: #includeExtrasForSTX put: something.
+options
+    "Return a snapshot options (as MCSnapshotOptions) with options
+     for the receiver. Options may be modified."
 
-    "Modified: / 12-08-2013 / 01:57:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    | options |
+    options := self objectAttributeAt: #options.
+    options isNil ifTrue:[ 
+        options := MCSnapshotOptions new.
+        options := self objectAttributeAt: #options put: options.
+    ].
+    ^ options
+
+    "Created: / 07-09-2015 / 15:24:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+options: aMCSnapshotOptions
+    self objectAttributeAt: #options put: aMCSnapshotOptions.
+
+    "Created: / 07-09-2015 / 15:26:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !MCSnapshot methodsFor:'converting'!
--- a/MCSnapshotBrowser.st	Thu Nov 03 13:22:28 2016 +0100
+++ b/MCSnapshotBrowser.st	Thu Nov 24 21:56:31 2016 +0000
@@ -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 Nov 03 13:22:28 2016 +0100
+++ /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 §'
-! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/MCSnapshotOptions.st	Thu Nov 24 21:56:31 2016 +0000
@@ -0,0 +1,26 @@
+"{ Package: 'stx:goodies/monticello' }"
+
+"{ NameSpace: Smalltalk }"
+
+Object subclass:#MCSnapshotOptions
+	instanceVariableNames:'includeExtrasForSTX'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'SCM-Monticello-Base'
+!
+
+!MCSnapshotOptions methodsFor:'accessing'!
+
+includeExtrasForSTX    
+    
+    "/ do not default to true here, as the version is snapshotted twice in order to
+    "/ update the version-strings, and we don not need this stuff in the first round!!
+    ^ includeExtrasForSTX ? false
+
+    "Modified: / 07-09-2015 / 15:22:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+includeExtrasForSTX:aBoolean
+    includeExtrasForSTX := aBoolean.
+! !
+
--- a/MCSnapshotResource.st	Thu Nov 03 13:22:28 2016 +0100
+++ /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 Nov 03 13:22:28 2016 +0100
+++ /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 Nov 03 13:22:28 2016 +0100
+++ /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 Nov 03 13:22:28 2016 +0100
+++ /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 §'
-! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/MCStXMczReader.st	Thu Nov 24 21:56:31 2016 +0000
@@ -0,0 +1,23 @@
+"{ Package: 'stx:goodies/monticello' }"
+
+"{ NameSpace: Smalltalk }"
+
+MCMczReader subclass:#MCStXMczReader
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'SCM-Monticello-St/X Storing'
+!
+
+!MCStXMczReader methodsFor:'accessing'!
+
+snapshot
+    | snapshot |
+
+    snapshot := super snapshot.
+    snapshot := MCStXSnapshotPostReadTransformation transform: snapshot.
+    ^ snapshot
+
+    "Created: / 10-05-2015 / 05:45:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
--- a/MCStXSnapshotPostReadTransformation.st	Thu Nov 03 13:22:28 2016 +0100
+++ b/MCStXSnapshotPostReadTransformation.st	Thu Nov 24 21:56:31 2016 +0000
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/monticello' }"
 
+"{ NameSpace: Smalltalk }"
+
 MCStXSnapshotTransformation subclass:#MCStXSnapshotPostReadTransformation
 	instanceVariableNames:''
 	classVariableNames:''
@@ -25,6 +27,21 @@
 "
 ! !
 
+!MCStXSnapshotPostReadTransformation methodsFor:'visiting'!
+
+visitMethodDefinition: definition
+    | source |
+
+    source := definition source asStringWithNativeLineEndings.  "/ Make sure source has native line endings
+    source := self class reindentUsingTabsAndSpaces: source.    "/ Make sure there are tabs and spaces used for indentation
+                                                                "/ (as it is norm on Smalltalk/X)
+    source := source asSingleByteStringIfPossible.              "/ Convert to single byte string
+
+    definition source: source.
+
+    "Created: / 24-04-2015 / 16:02:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
 !MCStXSnapshotPostReadTransformation class methodsFor:'documentation'!
 
 version
--- a/MCStXSnapshotPreWriteTransformation.st	Thu Nov 03 13:22:28 2016 +0100
+++ b/MCStXSnapshotPreWriteTransformation.st	Thu Nov 24 21:56:31 2016 +0000
@@ -1,11 +1,9 @@
-"{ Encoding: utf8 }"
-
 "{ Package: 'stx:goodies/monticello' }"
 
 "{ NameSpace: Smalltalk }"
 
 MCStXSnapshotTransformation subclass:#MCStXSnapshotPreWriteTransformation
-	instanceVariableNames:'extensionMethodCategoryMap projectDefinition'
+	instanceVariableNames:'extensionMethodCategoryMap projectDefinition includeExtrasForSTX'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'SCM-Monticello-St/X Storing'
@@ -106,6 +104,7 @@
 transform: anMCSnapshot
     "Returns a transformed **copy** of the original snapshot"
 
+    includeExtrasForSTX := anMCSnapshot options includeExtrasForSTX.
     extensionMethodCategoryMap := OrderedCollection new.
     original := anMCSnapshot.
     projectDefinition := self projectDefinition.
@@ -115,30 +114,32 @@
         ^transformed
     ].
     super transform: anMCSnapshot.
-    (projectDefinition notNil and:[extensionMethodCategoryMap notEmpty]) ifTrue:[
-        | source |
+    includeExtrasForSTX ifTrue:[
+        (projectDefinition notNil and:[extensionMethodCategoryMap notEmpty]) ifTrue:[
+            | source |
 
-        source :=
-            self monticelloSmalltalkXExtensionMethodCategories_Code bindWith:
-                (String streamContents:[:s|
-                    extensionMethodCategoryMap do:[:entry|
-                        s tab; tab; nextPutLine:  entry storeString
-                    ].
-                ]).
+            source :=
+                self monticelloSmalltalkXExtensionMethodCategories_Code bindWith:
+                    (String streamContents:[:s|
+                        extensionMethodCategoryMap do:[:entry|
+                            s tab; tab; nextPutLine:  entry storeString
+                        ].
+                    ]).
 
-         transformed definitions addFirst:
-            (MCMethodDefinition
-                className:  projectDefinition name
-                classIsMeta: true
-                selector: 'monticelloSmalltalkXExtensionMethodCategories'
-                category: 'accessing - monticello'
-                timeStamp: 'Generated by ', self class name , ' at ' , Timestamp now printString
-                source: source)
+             transformed definitions addFirst:
+                (MCMethodDefinition
+                    className:  projectDefinition name
+                    classIsMeta: true
+                    selector: 'monticelloSmalltalkXExtensionMethodCategories'
+                    category: 'accessing - monticello'
+                    timeStamp: 'Generated by ', self class name , ' at ' , Timestamp now printString
+                    source: source)
+        ].
     ].
     ^transformed.
 
     "Created: / 31-05-2013 / 00:05:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified (format): / 12-06-2013 / 09:23:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 07-09-2015 / 15:28:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !MCStXSnapshotPreWriteTransformation methodsFor:'visiting'!
@@ -153,31 +154,52 @@
 
     class := definition actualClass.
     class isProjectDefinition ifTrue:[
-        definition
-"/            className:(definition className capitalized);
-            superclassName: #Object;
-            category: class monticelloName.
+        includeExtrasForSTX ifTrue:[    
+            definition
+    "/            className:(definition className capitalized);
+                superclassName: #PackageManifest;
+                category: class monticelloName.
 
-        transformed definitions addFirst:
-            (MCMethodDefinition
-                className: definition className
-                classIsMeta: true
-                selector: 'monticelloProjectDefinitionTypeName'
-                category: 'accessing - monticello'
-                timeStamp: 'Generated by ', self class name , ' at ' , Timestamp now printString
-                source:
-                    (self monticelloSmalltalkXProjectType_Code bindWith: (class isApplicationDefinition ifTrue:[#application] ifFalse:[#library]) storeString))
+            transformed definitions addFirst:
+                (MCMethodDefinition
+                    className: definition className
+                    classIsMeta: true
+                    selector: 'monticelloProjectDefinitionTypeName'
+                    category: 'accessing - monticello'
+                    timeStamp: 'Generated by ', self class name , ' at ' , Timestamp now printString
+                    source:
+                        (self monticelloSmalltalkXProjectType_Code bindWith: (class isApplicationDefinition ifTrue:[#application] ifFalse:[#library]) storeString))
+        ] ifFalse:[ 
+            transformed definitions remove: definition.   
+        ].
     ]
 
     "Created: / 29-05-2013 / 12:19:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 20-09-2013 / 00:14:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 31-07-2015 / 09:22:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 visitMethodDefinition: definition
-    | source|
+    | class source |
 
-    source := definition source asStringWithNativeLineEndings asStringCollection withTabs asStringWithSqueakLineEndings.
-    source := source asSingleByteStringIfPossible.
+    includeExtrasForSTX ifFalse:[  
+        "/ If St/X extras should not be included, then remove all methods
+        "/ that belong to project definition class.
+        class := definition actualClass theNonMetaclass.
+        class == projectDefinition ifTrue:[ 
+            transformed definitions remove: definition.
+            ^ self.
+        ].
+        "/ Also, remove all version_XX methods
+        (AbstractSourceCodeManager isVersionMethodSelector: definition selector) ifTrue:[
+            transformed definitions remove: definition.
+        ]
+    ].
+
+    source := definition source asStringWithNativeLineEndings.  "/ Make sure source has native line endings
+    source := self class reindentUsingTabsOnly: source.         "/ Make sure there are only tabs (norm on Squeak / Pharo)
+    source := source asStringWithSqueakLineEndings.             "/ Make sure source has Squeak line endings
+    source := source asSingleByteStringIfPossible.              "/ Convert to single byte string
+
     definition source: source.
 
     (self isExtensionMethodDefinition: definition) ifTrue:[
@@ -195,7 +217,7 @@
     ].
 
     "Created: / 30-05-2013 / 22:48:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 06-11-2014 / 03:11:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 10-05-2015 / 15:08:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 visitOrganizationDefinition: defintion
@@ -220,5 +242,10 @@
 
 version_CVS
     ^ '$Header: /cvs/stx/stx/goodies/monticello/MCStXSnapshotPreWriteTransformation.st,v 1.11 2015-03-30 19:54:21 cg Exp $'
+!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
 ! !
 
--- a/MCStXSnapshotTransformation.st	Thu Nov 03 13:22:28 2016 +0100
+++ b/MCStXSnapshotTransformation.st	Thu Nov 24 21:56:31 2016 +0000
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/monticello' }"
 
+"{ NameSpace: Smalltalk }"
+
 Object subclass:#MCStXSnapshotTransformation
 	instanceVariableNames:'original transformed'
 	classVariableNames:''
@@ -49,6 +51,144 @@
     "Created: / 29-05-2013 / 11:36:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+!MCStXSnapshotTransformation class methodsFor:'utilities'!
+
+reindentUsingTabsAndSpaces: aString
+    "Reindent `aString` so the indentation is done using pelicular mixture
+     of tabs and spaces it is demanded by Claus Gittinger for Smalltalk/X 
+     code.
+
+     Assume `aString` is a method source an that it is indented using 
+     either tabs only or mixture of tabs and spaces.
+    "
+    | lines lineNr |
+
+    "First, detect which scheme is used..."
+    lines := aString asStringCollection.
+    lines size < 2 ifTrue:[ ^ aString ].
+    lineNr := 2.
+    [ 
+        lineNr <= lines size 
+            and: [ (lines at: lineNr) isEmptyOrNil ]
+    ] whileTrue:[ 
+        lineNr := lineNr + 1.
+    ].    
+    (lineNr > lines size or:[(lines at: lineNr) first == Character space]) ifTrue:[ 
+        "/ Indented by mixture, no need to do anything"
+        ^ aString
+    ] ifFalse:[ 
+        2 to: lines size do:[:lineNr |
+            | original expanded |
+
+            original := lines at: lineNr.
+            expanded := original class streamContents:[ :out |
+                | in tabs |
+
+
+                in := original readStream.
+                tabs := 0.
+                [ in peek == Character tab ] whileTrue:[
+                    in next.
+                    tabs := tabs + 1.
+                ].
+
+                false ifTrue:[ 
+                    "/ Use tabs, then spaces to indent.
+                    out next: tabs // 2 put: Character tab.
+                    (tabs \\ 2) ~~ 0 ifTrue:[ 
+                        out next: 4 put: Character space.
+                    ].
+                ] ifFalse:[ 
+                    "/ Use spaces only - it seems that St/X fileout does that now...
+                    out next: tabs * 4 put: Character space.            
+                ].
+                [ in atEnd ] whileFalse:[
+                    out nextPut: in next.
+                ].
+            ].  
+            lines at: lineNr put: expanded.  
+        ].
+    ].
+    ^ lines asStringWithoutFinalCR.
+
+    "
+    | s |
+
+    s := (MCStXSnapshotTransformation class >> #reindentUsingTabsOnly:) source.
+    self assert: (MCStXSnapshotTransformation reindentUsingTabsAndSpaces: (MCStXSnapshotTransformation reindentUsingTabsOnly: s)) = s
+    "
+
+    "Created: / 24-04-2015 / 14:36:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 29-04-2015 / 22:32:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+reindentUsingTabsOnly: aString
+    "Reindent `aString` so the indentation is done using tabs only,
+     as it is norm on Squeak / Pharo.
+
+     Assume `aString` is a method source an that it is indented using 
+     either tabs only or using arcane Smalltalk/X space/tab mixture.
+    "
+    | lines lineNr |
+
+    "First, detect which scheme is used..."
+    lines := aString asStringCollection.
+    lines size < 2 ifTrue:[ ^ aString ].
+    lineNr := 2.
+    [ 
+        lineNr <= lines size 
+            and: [ (lines at: lineNr) isEmptyOrNil ]
+    ] whileTrue:[ 
+        lineNr := lineNr + 1.
+    ].
+    (lineNr > lines size or:[(lines at: lineNr) first == Character tab]) ifTrue:[ 
+        "/ Indented by tabs, no need to do anything"
+        ^ aString
+    ] ifFalse:[ 
+        2 to: lines size do:[:lineNr |
+            | original expanded |
+
+            original := lines at: lineNr.
+            expanded := original class streamContents:[ :out |
+                | in nonWhitespaceSeen |
+
+
+                in := original readStream.
+                nonWhitespaceSeen := false.
+                [ in atEnd not and:[nonWhitespaceSeen not] ] whileTrue:[  
+                    | spaces |
+
+                    spaces := 0.
+                    [ in peek == Character tab ] whileTrue:[
+                        in next.
+                        out nextPut: Character tab; nextPut: Character tab.
+                    ].
+                    [ in peek == Character space ] whileTrue:[
+                        in next.
+                        spaces := spaces + 1.
+                    ].
+                    out next: spaces // 4 put: Character tab.
+                    out next: spaces \\ 4 put: Character space.
+                    nonWhitespaceSeen := (in peek == Character tab or:[ in peek == Character space ]) not.
+                ].
+                [ in atEnd ] whileFalse:[
+                    out nextPut: in next.
+                ].
+            ].  
+            lines at: lineNr put: expanded.  
+        ].
+    ].
+    ^ lines asStringWithoutFinalCR.
+
+    "
+    MCStXSnapshotTransformation reindentUsingTabs:
+        (MCStXSnapshotTransformation class >> #reindentUsingTabs:) source
+    "
+
+    "Created: / 24-04-2015 / 14:36:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 29-04-2015 / 22:31:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
 !MCStXSnapshotTransformation methodsFor:'accessing'!
 
 original
@@ -118,5 +258,10 @@
 
 version_CVS
     ^ '$Header: /cvs/stx/stx/goodies/monticello/MCStXSnapshotTransformation.st,v 1.2 2013-05-30 23:35:33 vrany Exp $'
+!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
 ! !
 
--- a/MCStxMczWriter.st	Thu Nov 03 13:22:28 2016 +0100
+++ b/MCStxMczWriter.st	Thu Nov 24 21:56:31 2016 +0000
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/monticello' }"
 
+"{ NameSpace: Smalltalk }"
+
 MCMczWriter subclass:#MCStxMczWriter
 	instanceVariableNames:''
 	classVariableNames:''
@@ -20,6 +22,14 @@
 "
 ! !
 
+!MCStxMczWriter class methodsFor:'as yet unclassified'!
+
+readerClass
+    ^ MCStXMczReader
+
+    "Created: / 10-05-2015 / 05:46:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
 !MCStxMczWriter methodsFor:'accessing'!
 
 snapshotWriterClass
@@ -119,14 +129,14 @@
         ,  (self serializeDefinitions: snapshot definitions).
 
     self addString: source at: 'snapshot/source.', self snapshotWriterClass extension.
-    "/ I whink, we can comment the following (or is it compatible?)
+    "/ CG: I think, we can comment the following (or is it compatible?)
 
     "/ JV: 
     "/ NO, DON'T DO IT!! snapshot.bin is THE ONLY thing that Pharo/Squeak reads.
     "/ It does not care about snapshot/source.st, actually
     self addString: (self serializeInBinary: snapshot) at: 'snapshot.bin'
 
-    "Modified (comment): / 29-05-2013 / 12:06:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified (comment): / 31-07-2015 / 08:59:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 writeVersion: aVersion
@@ -134,7 +144,7 @@
 
     super writeVersion: aVersion.
 
-    aVersion snapshot includeExtrasForSTX ifTrue:[
+    aVersion snapshot options includeExtrasForSTX ifTrue:[
         "/ ST/X specific stuff here.
 
         packageID := aVersion package name.
@@ -149,6 +159,8 @@
             self writeResourceFiles: aVersion for: prjDef.
         ]
     ]
+
+    "Modified: / 07-09-2015 / 15:28:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !MCStxMczWriter class methodsFor:'documentation'!
@@ -159,5 +171,10 @@
 
 version_CVS
     ^ '$Header: /cvs/stx/stx/goodies/monticello/MCStxMczWriter.st,v 1.6 2013-05-29 11:47:31 vrany Exp $'
+!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
 ! !
 
--- a/MCTestCase.st	Thu Nov 03 13:22:28 2016 +0100
+++ /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 Nov 03 13:22:28 2016 +0100
+++ b/MCToolWindowBuilder.st	Thu Nov 24 21:56:31 2016 +0000
@@ -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/MCVersionInfo.st	Thu Nov 03 13:22:28 2016 +0100
+++ b/MCVersionInfo.st	Thu Nov 24 21:56:31 2016 +0000
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/monticello' }"
 
+"{ NameSpace: Smalltalk }"
+
 MCAncestry subclass:#MCVersionInfo
 	instanceVariableNames:'id name message date time author'
 	classVariableNames:''
@@ -39,6 +41,29 @@
 
 !MCVersionInfo methodsFor:'accessing'!
 
+inspector2TabAncestry
+    <inspector2Tab>
+
+    ^ (self newInspector2Tab)
+        label:'Ancestry';
+        priority:50;
+        view: [
+            | list view |
+
+            list := PluggableHierarchicalList new.
+            list childBlock: [ :parent | parent ancestors ].
+            list labelBlock: [ :child | child name ].
+            list root: self.
+            view := ScrollableView for:HierarchicalListView.
+            view useDefaultIcons: false.
+            view list: list.
+            view
+        ];
+        yourself
+
+    "Created: / 07-09-2015 / 15:38:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 message
 	^ message ifNil: ['']
 !
@@ -112,6 +137,53 @@
 		at: #author put: author;
 		at: #ancestors put: (self ancestors collect: [:a | a asDictionary]);
 		yourself
+!
+
+fromLiteralArrayEncoding: encoding
+    name := encoding at: 3.
+    id := UUID fromString: (encoding at: 5).
+    date := Date readFrom:(encoding at: 7) format: '%y-%m-%d'.
+    time := Time readFrom:(encoding at: 9) format: '%H:%m:%s.%i'.
+    author :=  encoding at: 11.
+    message := (encoding at: 13) asStringWithSqueakLineEndings.     
+    encoding size > 13 ifTrue:[
+        ancestors := (encoding at: 15) collect:[ :e | e decodeAsLiteralArray ].
+    ].
+
+    "Created: / 07-09-2015 / 17:36:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 08-09-2015 / 00:02:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+literalArrayEncoding
+    ^ self literalArrayEncodingWithAncestors: true
+
+    "Created: / 07-09-2015 / 17:23:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+literalArrayEncodingWithAncestors: withAncestors
+    | encoding |
+    encoding := Array new: 13 + (withAncestors ifTrue:[2] ifFalse:[0]).
+    encoding
+        at: 1 put: MCVersionInfo name;
+        at: 2 put: #name:; at: 3 put: name;
+        at: 4 put: #id:; at: 5 put: id printString;
+        at: 6 put: #date:; at: 7 put: (date printStringFormat:'%y-%m-%d');
+        at: 8 put: #time:; at: 9 put: (time printStringFormat:'%H:%m:%s.%i');
+        at:10 put: #author:; at: 11 put: author;
+        at:12 put: #message:; at: 13 put: (message asStringWithNativeLineEndings).
+    withAncestors ifTrue:[    
+        encoding at:14 put: #ancestors:; at: 15 put: (withAncestors ifTrue:[self ancestors collect:[ :e|e literalArrayEncodingWithAncestors: withAncestors ] as: Array] ifFalse:[ #() ]).
+    ].
+    ^ encoding.
+
+    "Created: / 07-09-2015 / 17:22:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 08-09-2015 / 00:00:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+literalArrayEncodingWithoutAncestors
+    ^ self literalArrayEncodingWithAncestors: false
+
+    "Created: / 07-09-2015 / 17:47:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !MCVersionInfo methodsFor:'initialize-release'!
@@ -164,3 +236,4 @@
 version
     ^ '$Header: /cvs/stx/stx/goodies/monticello/MCVersionInfo.st,v 1.4 2012-09-11 21:30:28 cg Exp $'
 ! !
+
--- a/MCVersionInfoWriter.st	Thu Nov 03 13:22:28 2016 +0100
+++ b/MCVersionInfoWriter.st	Thu Nov 24 21:56:31 2016 +0000
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/monticello' }"
 
+"{ NameSpace: Smalltalk }"
+
 MCWriter subclass:#MCVersionInfoWriter
 	instanceVariableNames:'written'
 	classVariableNames:''
@@ -11,7 +13,9 @@
 !MCVersionInfoWriter methodsFor:'as yet unclassified'!
 
 isWritten: aVersionInfo
-	^ self written includes: aVersionInfo
+        ^ self written includes: aVersionInfo id
+
+    "Modified: / 08-09-2015 / 00:19:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 writeVersionInfo: aVersionInfo
@@ -20,9 +24,18 @@
         stream nextPut: $(.
         #(name message id date time author) 
                 do: [:sel | 
+                        | value |
                         stream nextPutAll: sel.
                         stream nextPut: Character space.
-                        ((aVersionInfo perform: sel) ifNil: ['']) printString storeOn: stream.
+
+                        "/ A special hack for Date - use concrete format known to parse well
+                        "/ in Pharo/Squeak
+                        value := (aVersionInfo perform: sel).
+                        (value notNil and:[sel == #date]) ifTrue:[ 
+                            (value printStringFormat:'%D %(MonthName) %y' language: #en) storeOn: stream  
+                        ] ifFalse:[ 
+                            (value ?'') printString storeOn: stream.
+                        ].
                         stream nextPut: $ ].
         stream nextPutAll: 'ancestors ('.
         aVersionInfo ancestors do: [:ea | self writeVersionInfo: ea].
@@ -31,7 +44,7 @@
         stream nextPutAll: '))'.
         self wrote: aVersionInfo
 
-    "Modified: / 11-06-2013 / 02:55:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 23-04-2015 / 15:01:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 written
@@ -39,7 +52,9 @@
 !
 
 wrote: aVersionInfo
-	self written add: aVersionInfo
+        self written add: aVersionInfo id
+
+    "Modified: / 08-09-2015 / 00:19:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !MCVersionInfoWriter class methodsFor:'documentation'!
@@ -52,6 +67,11 @@
     ^ '$Header: /cvs/stx/stx/goodies/monticello/MCVersionInfoWriter.st,v 1.6 2013-06-11 01:58:56 vrany Exp $'
 !
 
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+!
+
 version_SVN
     ^ '$Id: MCVersionInfoWriter.st,v 1.6 2013-06-11 01:58:56 vrany Exp $'
 ! !
--- a/MCVersionTest.st	Thu Nov 03 13:22:28 2016 +0100
+++ /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/MCWorkingAncestry.st	Thu Nov 03 13:22:28 2016 +0100
+++ b/MCWorkingAncestry.st	Thu Nov 24 21:56:31 2016 +0000
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/monticello' }"
 
+"{ NameSpace: Smalltalk }"
+
 MCAncestry subclass:#MCWorkingAncestry
 	instanceVariableNames:''
 	classVariableNames:''
@@ -11,6 +13,12 @@
 !
 
 
+!MCWorkingAncestry methodsFor:'accessing'!
+
+ancestors:aCollection
+    ancestors := aCollection.
+! !
+
 !MCWorkingAncestry methodsFor:'as yet unclassified'!
 
 addAncestor: aNode
@@ -53,3 +61,4 @@
 version
     ^ '$Header: /cvs/stx/stx/goodies/monticello/MCWorkingAncestry.st,v 1.3 2012-09-11 21:31:23 cg Exp $'
 ! !
+
--- a/MCWorkingCopyBrowser.st	Thu Nov 03 13:22:28 2016 +0100
+++ b/MCWorkingCopyBrowser.st	Thu Nov 24 21:56:31 2016 +0000
@@ -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 Nov 03 13:22:28 2016 +0100
+++ /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 Nov 03 13:22:28 2016 +0100
+++ b/MCWorkingHistoryBrowser.st	Thu Nov 24 21:56:31 2016 +0000
@@ -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 Nov 03 13:22:28 2016 +0100
+++ b/Make.proto	Thu Nov 24 21:56:31 2016 +0000
@@ -1,4 +1,4 @@
-# $Header: /cvs/stx/stx/goodies/monticello/Make.proto,v 1.19 2014-12-23 19:18:03 cg Exp $
+# $Header$
 #
 # DO NOT EDIT
 # automagically generated from the projectDefinition: stx_goodies_monticello.
@@ -34,7 +34,7 @@
 # add the path(es) here:,
 # ********** OPTIONAL: MODIFY the next lines ***
 # LOCALINCLUDES=-Ifoo -Ibar
-LOCALINCLUDES= -I$(INCLUDE_TOP)/stx/goodies/communication -I$(INCLUDE_TOP)/stx/libbasic -I$(INCLUDE_TOP)/stx/libbasic3 -I$(INCLUDE_TOP)/stx/libcompat -I$(INCLUDE_TOP)/stx/libtool -I$(INCLUDE_TOP)/stx/libview2 -I$(INCLUDE_TOP)/stx/libwidg2
+LOCALINCLUDES= -I$(INCLUDE_TOP)/stx/goodies/communication -I$(INCLUDE_TOP)/stx/libbasic -I$(INCLUDE_TOP)/stx/libbasic2 -I$(INCLUDE_TOP)/stx/libbasic3 -I$(INCLUDE_TOP)/stx/libcomp -I$(INCLUDE_TOP)/stx/libcompat -I$(INCLUDE_TOP)/stx/libhtml -I$(INCLUDE_TOP)/stx/libscm/mercurial -I$(INCLUDE_TOP)/stx/libtool -I$(INCLUDE_TOP)/stx/libview -I$(INCLUDE_TOP)/stx/libview2 -I$(INCLUDE_TOP)/stx/libwidg -I$(INCLUDE_TOP)/stx/libwidg2
 
 
 # if you need any additional defines for embedded C code,
@@ -70,6 +70,13 @@
 
 
 
+# Enforce recompilation of package definition class if Mercurial working
+# copy state changes. Together with --guessVersion it ensures that package
+# definition class always contains correct binary revision string.
+ifneq (**NOHG**, $(shell hg root 2> /dev/null || echo -n '**NOHG**'))
+stx_goodies_monticello.$(O): $(shell hg root)/.hg/dirstate
+endif
+
 
 
 
@@ -102,7 +109,6 @@
 	cd ../../libui && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
 	cd ../../libview && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
 	cd ../../libview2 && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
-	cd ../sunit && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
 	cd ../../libwidg && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
 	cd ../../libwidg2 && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
 	cd ../../libcompat && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES)"
@@ -151,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)
@@ -160,11 +166,12 @@
 $(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)
 $(OUTDIR)MCSnapshot.$(O) MCSnapshot.$(H): MCSnapshot.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)MCSnapshotOptions.$(O) MCSnapshotOptions.$(H): MCSnapshotOptions.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)MCSourceCodeManager.$(O) MCSourceCodeManager.$(H): MCSourceCodeManager.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic3/AbstractSourceCodeManager.$(H) $(STCHDR)
 $(OUTDIR)MCStXNamespaceQuery.$(O) MCStXNamespaceQuery.$(H): MCStXNamespaceQuery.st $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Notification.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/Query.$(H) $(STCHDR)
 $(OUTDIR)MCStXPackageInfo.$(O) MCStXPackageInfo.$(H): MCStXPackageInfo.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libcompat/PackageInfo.$(H) $(STCHDR)
@@ -176,7 +183,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)
@@ -249,6 +256,7 @@
 $(OUTDIR)MCTraitDefinition.$(O) MCTraitDefinition.$(H): MCTraitDefinition.st $(INCLUDE_TOP)/stx/goodies/monticello/MCClassDefinition.$(H) $(INCLUDE_TOP)/stx/goodies/monticello/MCDefinition.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)MCCacheRepository.$(O) MCCacheRepository.$(H): MCCacheRepository.st $(INCLUDE_TOP)/stx/goodies/monticello/MCDirectoryRepository.$(H) $(INCLUDE_TOP)/stx/goodies/monticello/MCFileBasedRepository.$(H) $(INCLUDE_TOP)/stx/goodies/monticello/MCRepository.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)MCMcdReader.$(O) MCMcdReader.$(H): MCMcdReader.st $(INCLUDE_TOP)/stx/goodies/monticello/MCMczReader.$(H) $(INCLUDE_TOP)/stx/goodies/monticello/MCReader.$(H) $(INCLUDE_TOP)/stx/goodies/monticello/MCVersionReader.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)MCStXMczReader.$(O) MCStXMczReader.$(H): MCStXMczReader.st $(INCLUDE_TOP)/stx/goodies/monticello/MCMczReader.$(H) $(INCLUDE_TOP)/stx/goodies/monticello/MCReader.$(H) $(INCLUDE_TOP)/stx/goodies/monticello/MCVersionReader.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)MCSubDirectoryRepository.$(O) MCSubDirectoryRepository.$(H): MCSubDirectoryRepository.st $(INCLUDE_TOP)/stx/goodies/monticello/MCDirectoryRepository.$(H) $(INCLUDE_TOP)/stx/goodies/monticello/MCFileBasedRepository.$(H) $(INCLUDE_TOP)/stx/goodies/monticello/MCRepository.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)extensions.$(O): extensions.st $(INCLUDE_TOP)/stx/libbasic/AbstractTime.$(H) $(INCLUDE_TOP)/stx/libbasic/Annotation.$(H) $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/Behavior.$(H) $(INCLUDE_TOP)/stx/libbasic/CharacterArray.$(H) $(INCLUDE_TOP)/stx/libbasic/Class.$(H) $(INCLUDE_TOP)/stx/libbasic/ClassDescription.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Dictionary.$(H) $(INCLUDE_TOP)/stx/libbasic/IdentityDictionary.$(H) $(INCLUDE_TOP)/stx/libbasic/Magnitude.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/OrderedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/ProjectDefinition.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/Set.$(H) $(INCLUDE_TOP)/stx/libbasic/Stream.$(H) $(INCLUDE_TOP)/stx/libbasic/String.$(H) $(INCLUDE_TOP)/stx/libbasic/StringCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/Symbol.$(H) $(INCLUDE_TOP)/stx/libbasic/Timestamp.$(H) $(INCLUDE_TOP)/stx/libbasic/UndefinedObject.$(H) $(INCLUDE_TOP)/stx/libbasic/UninterpretedBytes.$(H) $(INCLUDE_TOP)/stx/libbasic/UserPreferences.$(H) $(INCLUDE_TOP)/stx/libbasic3/Change.$(H) $(INCLUDE_TOP)/stx/libbasic3/VersionInfo.$(H) $(INCLUDE_TOP)/stx/libcompat/PackageInfo.$(H) $(INCLUDE_TOP)/stx/libtool/SystemBrowser.$(H) $(INCLUDE_TOP)/stx/libtool/Tools__NewSystemBrowser.$(H) $(INCLUDE_TOP)/stx/libview2/ApplicationModel.$(H) $(INCLUDE_TOP)/stx/libview2/Model.$(H) $(STCHDR)
 
--- a/Make.spec	Thu Nov 03 13:22:28 2016 +0100
+++ b/Make.spec	Thu Nov 24 21:56:31 2016 +0000
@@ -1,4 +1,4 @@
-# $Header: /cvs/stx/stx/goodies/monticello/Make.spec,v 1.20 2014-12-23 19:17:59 cg Exp $
+# $Header$
 #
 # DO NOT EDIT
 # automagically generated from the projectDefinition: stx_goodies_monticello.
@@ -90,6 +90,7 @@
 	MCScanner \
 	MCSettingsApp \
 	MCSnapshot \
+	MCSnapshotOptions \
 	MCSourceCodeManager \
 	MCStXNamespaceQuery \
 	MCStXPackageInfo \
@@ -174,6 +175,7 @@
 	MCTraitDefinition \
 	MCCacheRepository \
 	MCMcdReader \
+	MCStXMczReader \
 	MCSubDirectoryRepository \
 
 
@@ -219,6 +221,7 @@
     $(OUTDIR_SLASH)MCScanner.$(O) \
     $(OUTDIR_SLASH)MCSettingsApp.$(O) \
     $(OUTDIR_SLASH)MCSnapshot.$(O) \
+    $(OUTDIR_SLASH)MCSnapshotOptions.$(O) \
     $(OUTDIR_SLASH)MCSourceCodeManager.$(O) \
     $(OUTDIR_SLASH)MCStXNamespaceQuery.$(O) \
     $(OUTDIR_SLASH)MCStXPackageInfo.$(O) \
@@ -303,6 +306,7 @@
     $(OUTDIR_SLASH)MCTraitDefinition.$(O) \
     $(OUTDIR_SLASH)MCCacheRepository.$(O) \
     $(OUTDIR_SLASH)MCMcdReader.$(O) \
+    $(OUTDIR_SLASH)MCStXMczReader.$(O) \
     $(OUTDIR_SLASH)MCSubDirectoryRepository.$(O) \
     $(OUTDIR_SLASH)extensions.$(O) \
 
--- a/abbrev.stc	Thu Nov 03 13:22:28 2016 +0100
+++ b/abbrev.stc	Thu Nov 24 21:56:31 2016 +0000
@@ -41,6 +41,7 @@
 MCScanner MCScanner stx:goodies/monticello 'SCM-Monticello-Chunk Format' 0
 MCSettingsApp MCSettingsApp stx:goodies/monticello 'SCM-Monticello-St/X UI' 1
 MCSnapshot MCSnapshot stx:goodies/monticello 'SCM-Monticello-Base' 0
+MCSnapshotOptions MCSnapshotOptions stx:goodies/monticello 'SCM-Monticello-Base' 0
 MCSourceCodeManager MCSourceCodeManager stx:goodies/monticello 'SCM-Monticello-St/X support' 0
 MCStXNamespaceQuery MCStXNamespaceQuery stx:goodies/monticello 'SCM-Monticello-St/X support' 1
 MCStXPackageInfo MCStXPackageInfo stx:goodies/monticello 'SCM-Monticello-St/X support' 0
@@ -135,4 +136,5 @@
 MCChangeSelector MCChangeSelector stx:goodies/monticello 'SCM-Monticello-UI' 0
 MCMcdReader MCMcdReader stx:goodies/monticello 'SCM-Monticello-Storing' 0
 MCMergeBrowser MCMergeBrowser stx:goodies/monticello 'SCM-Monticello-UI' 0
+MCStXMczReader MCStXMczReader stx:goodies/monticello 'SCM-Monticello-St/X Storing' 0
 MCSubDirectoryRepository MCSubDirectoryRepository stx:goodies/monticello 'SCM-Monticello-Repositories' 0
--- a/bc.mak	Thu Nov 03 13:22:28 2016 +0100
+++ b/bc.mak	Thu Nov 24 21:56:31 2016 +0000
@@ -1,4 +1,4 @@
-# $Header: /cvs/stx/stx/goodies/monticello/bc.mak,v 1.21 2014-12-23 19:18:08 cg Exp $
+# $Header$
 #
 # DO NOT EDIT
 # automagically generated from the projectDefinition: stx_goodies_monticello.
@@ -35,7 +35,7 @@
 
 
 
-LOCALINCLUDES= -I$(INCLUDE_TOP)\stx\goodies\communication -I$(INCLUDE_TOP)\stx\libbasic -I$(INCLUDE_TOP)\stx\libbasic3 -I$(INCLUDE_TOP)\stx\libcompat -I$(INCLUDE_TOP)\stx\libtool -I$(INCLUDE_TOP)\stx\libview2 -I$(INCLUDE_TOP)\stx\libwidg2
+LOCALINCLUDES= -I$(INCLUDE_TOP)\stx\goodies\communication -I$(INCLUDE_TOP)\stx\libbasic -I$(INCLUDE_TOP)\stx\libbasic2 -I$(INCLUDE_TOP)\stx\libbasic3 -I$(INCLUDE_TOP)\stx\libcomp -I$(INCLUDE_TOP)\stx\libcompat -I$(INCLUDE_TOP)\stx\libhtml -I$(INCLUDE_TOP)\stx\libscm\mercurial -I$(INCLUDE_TOP)\stx\libtool -I$(INCLUDE_TOP)\stx\libview -I$(INCLUDE_TOP)\stx\libview2 -I$(INCLUDE_TOP)\stx\libwidg -I$(INCLUDE_TOP)\stx\libwidg2
 LOCALDEFINES=
 
 STCLOCALOPT=-package=$(PACKAGE) -I. $(LOCALINCLUDES) -headerDir=. $(STCLOCALOPTIMIZATIONS) $(STCWARNINGS) $(LOCALDEFINES)  -varPrefix=$(LIBNAME)
@@ -59,7 +59,6 @@
 	pushd ..\..\libui & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
 	pushd ..\..\libview & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
 	pushd ..\..\libview2 & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
-	pushd ..\sunit & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
 	pushd ..\..\libwidg & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
 	pushd ..\..\libwidg2 & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
 	pushd ..\..\libcompat & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "
@@ -105,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)
@@ -114,11 +113,12 @@
 $(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)
 $(OUTDIR)MCSnapshot.$(O) MCSnapshot.$(H): MCSnapshot.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)MCSnapshotOptions.$(O) MCSnapshotOptions.$(H): MCSnapshotOptions.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)MCSourceCodeManager.$(O) MCSourceCodeManager.$(H): MCSourceCodeManager.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic3\AbstractSourceCodeManager.$(H) $(STCHDR)
 $(OUTDIR)MCStXNamespaceQuery.$(O) MCStXNamespaceQuery.$(H): MCStXNamespaceQuery.st $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Notification.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\Query.$(H) $(STCHDR)
 $(OUTDIR)MCStXPackageInfo.$(O) MCStXPackageInfo.$(H): MCStXPackageInfo.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcompat\PackageInfo.$(H) $(STCHDR)
@@ -130,7 +130,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)
@@ -203,7 +203,17 @@
 $(OUTDIR)MCTraitDefinition.$(O) MCTraitDefinition.$(H): MCTraitDefinition.st $(INCLUDE_TOP)\stx\goodies\monticello\MCClassDefinition.$(H) $(INCLUDE_TOP)\stx\goodies\monticello\MCDefinition.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)MCCacheRepository.$(O) MCCacheRepository.$(H): MCCacheRepository.st $(INCLUDE_TOP)\stx\goodies\monticello\MCDirectoryRepository.$(H) $(INCLUDE_TOP)\stx\goodies\monticello\MCFileBasedRepository.$(H) $(INCLUDE_TOP)\stx\goodies\monticello\MCRepository.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)MCMcdReader.$(O) MCMcdReader.$(H): MCMcdReader.st $(INCLUDE_TOP)\stx\goodies\monticello\MCMczReader.$(H) $(INCLUDE_TOP)\stx\goodies\monticello\MCReader.$(H) $(INCLUDE_TOP)\stx\goodies\monticello\MCVersionReader.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)MCStXMczReader.$(O) MCStXMczReader.$(H): MCStXMczReader.st $(INCLUDE_TOP)\stx\goodies\monticello\MCMczReader.$(H) $(INCLUDE_TOP)\stx\goodies\monticello\MCReader.$(H) $(INCLUDE_TOP)\stx\goodies\monticello\MCVersionReader.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)MCSubDirectoryRepository.$(O) MCSubDirectoryRepository.$(H): MCSubDirectoryRepository.st $(INCLUDE_TOP)\stx\goodies\monticello\MCDirectoryRepository.$(H) $(INCLUDE_TOP)\stx\goodies\monticello\MCFileBasedRepository.$(H) $(INCLUDE_TOP)\stx\goodies\monticello\MCRepository.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)extensions.$(O): extensions.st $(INCLUDE_TOP)\stx\libbasic\AbstractTime.$(H) $(INCLUDE_TOP)\stx\libbasic\Annotation.$(H) $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\Behavior.$(H) $(INCLUDE_TOP)\stx\libbasic\CharacterArray.$(H) $(INCLUDE_TOP)\stx\libbasic\Class.$(H) $(INCLUDE_TOP)\stx\libbasic\ClassDescription.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Dictionary.$(H) $(INCLUDE_TOP)\stx\libbasic\IdentityDictionary.$(H) $(INCLUDE_TOP)\stx\libbasic\Magnitude.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\OrderedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\ProjectDefinition.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\Set.$(H) $(INCLUDE_TOP)\stx\libbasic\Stream.$(H) $(INCLUDE_TOP)\stx\libbasic\String.$(H) $(INCLUDE_TOP)\stx\libbasic\StringCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\Symbol.$(H) $(INCLUDE_TOP)\stx\libbasic\Timestamp.$(H) $(INCLUDE_TOP)\stx\libbasic\UndefinedObject.$(H) $(INCLUDE_TOP)\stx\libbasic\UninterpretedBytes.$(H) $(INCLUDE_TOP)\stx\libbasic\UserPreferences.$(H) $(INCLUDE_TOP)\stx\libbasic3\Change.$(H) $(INCLUDE_TOP)\stx\libbasic3\VersionInfo.$(H) $(INCLUDE_TOP)\stx\libcompat\PackageInfo.$(H) $(INCLUDE_TOP)\stx\libtool\SystemBrowser.$(H) $(INCLUDE_TOP)\stx\libtool\Tools__NewSystemBrowser.$(H) $(INCLUDE_TOP)\stx\libview2\ApplicationModel.$(H) $(INCLUDE_TOP)\stx\libview2\Model.$(H) $(STCHDR)
 
 # ENDMAKEDEPEND --- do not remove this line
+
+# **Must be at end**
+
+# Enforce recompilation of package definition class if Mercurial working
+# copy state changes. Together with --guessVersion it ensures that package
+# definition class always contains correct binary revision string.
+!IFDEF HGROOT
+$(OUTDIR)stx_goodies_monticello.$(O): $(HGROOT)\.hg\dirstate
+!ENDIF
--- a/bmake.bat	Thu Nov 03 13:22:28 2016 +0100
+++ b/bmake.bat	Thu Nov 24 21:56:31 2016 +0000
@@ -4,9 +4,7 @@
 @REM do not edit - automatically generated from ProjectDefinition
 @REM -------
 @SET DEFINES=
-@REM Kludge got Mercurial, cannot be implemented in Borland make
-@FOR /F "tokens=*" %%i in ('hg root') do SET HGROOT=%%i
-@IF "%HGROOT%" NEQ "" SET DEFINES=%DEFINES% "-DHGROOT=%HGROOT%"
+
 make.exe -N -f bc.mak  %DEFINES% %*
 
 
--- a/extensions.st	Thu Nov 03 13:22:28 2016 +0100
+++ b/extensions.st	Thu Nov 24 21:56:31 2016 +0000
@@ -207,6 +207,65 @@
     "Created: / 07-06-2013 / 01:48:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+!ProjectDefinition class methodsFor:'accessing - monticello'!
+
+monticelloSplicemap
+    "Return a splicemap for this package. This is used to forge a 
+     'fake' ancestor when generating ancestry information out of 
+     Mercurial (or anyt other) history. This should make merging 
+     back into Squeak/Pharo a little easier as Monticello can (in theory)
+     find a proper ancestor. 
+
+     All this requires monticelloSplicemap being updated each time a code
+     is merged from Monticello.
+
+     The format of splicemap is a flat array of pairs 
+     (commit id, MCVersionInfo to splice) as literal encoding.
+    "
+    ^#()
+
+    "Created: / 07-09-2015 / 18:11:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!ProjectDefinition class methodsFor:'code generation'!
+
+monticelloSplicemap_code
+    ^ self monticelloSplicemap_codeFor:self monticelloSplicemap
+
+    "Created: / 07-09-2015 / 17:58:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!ProjectDefinition class methodsFor:'code generation'!
+
+monticelloSplicemap_codeFor:splicemap 
+    ^ String 
+        streamContents:[:s | 
+            s nextPutLine:'monticelloSplicemap'.
+            s
+                nextPutAll:'    "';
+                nextPutAll:(self class superclass lookupMethodFor:#monticelloSplicemap) 
+                            comment;
+                nextPutLine:'"'.
+            s nextPutLine:''.
+            s nextPutLine:'    ^ #('.
+            splicemap 
+                pairWiseDo:[:changeset :mcversion | 
+                    s nextPutAll:'        '.
+                    changeset storeOn:s.
+                    s space.
+                    mcversion storeOn:s.
+                    s
+                        cr;
+                        cr.
+                ].
+            s nextPutLine:'    )'
+        ].
+
+    "
+     stx_goodies_petitparser_compiler monticelloSplicemap_code"
+    "Created: / 07-09-2015 / 17:58:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
 !ProjectDefinition class methodsFor:'code generation'!
 
 monticelloTimestamps_code
@@ -473,7 +532,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/libInit.cc	Thu Nov 03 13:22:28 2016 +0100
+++ b/libInit.cc	Thu Nov 24 21:56:31 2016 +0000
@@ -1,5 +1,5 @@
 /*
- * $Header: /cvs/stx/stx/goodies/monticello/libInit.cc,v 1.20 2014-12-23 19:18:22 cg Exp $
+ * $Header$
  *
  * DO NOT EDIT
  * automagically generated from the projectDefinition: stx_goodies_monticello.
@@ -66,6 +66,7 @@
 _MCScanner_Init(pass,__pRT__,snd);
 _MCSettingsApp_Init(pass,__pRT__,snd);
 _MCSnapshot_Init(pass,__pRT__,snd);
+_MCSnapshotOptions_Init(pass,__pRT__,snd);
 _MCSourceCodeManager_Init(pass,__pRT__,snd);
 _MCStXNamespaceQuery_Init(pass,__pRT__,snd);
 _MCStXPackageInfo_Init(pass,__pRT__,snd);
@@ -150,6 +151,7 @@
 _MCTraitDefinition_Init(pass,__pRT__,snd);
 _MCCacheRepository_Init(pass,__pRT__,snd);
 _MCMcdReader_Init(pass,__pRT__,snd);
+_MCStXMczReader_Init(pass,__pRT__,snd);
 _MCSubDirectoryRepository_Init(pass,__pRT__,snd);
 
 _stx_137goodies_137monticello_extensions_Init(pass,__pRT__,snd);
--- a/mingwmake.bat	Thu Nov 03 13:22:28 2016 +0100
+++ b/mingwmake.bat	Thu Nov 24 21:56:31 2016 +0000
@@ -4,9 +4,6 @@
 @REM do not edit - automatically generated from ProjectDefinition
 @REM -------
 @SET DEFINES=
-@REM Kludge got Mercurial, cannot be implemented in Borland make
-@FOR /F "tokens=*" %%i in ('hg root') do SET HGROOT=%%i
-@IF "%HGROOT%" NEQ "" SET DEFINES=%DEFINES% "-DHGROOT=%HGROOT%"
 
 @pushd ..\..\rules
 @call find_mingw.bat
--- a/stx_goodies_monticello.st	Thu Nov 03 13:22:28 2016 +0100
+++ b/stx_goodies_monticello.st	Thu Nov 24 21:56:31 2016 +0000
@@ -33,34 +33,51 @@
 !
 
 mandatoryPreRequisites
-    "list all required mandatory packages.
-     Packages are mandatory, if they contain superclasses of the package's classes
-     or classes which are extended by this package.
-     This list can be maintained manually or (better) generated and
-     updated by scanning the superclass hierarchies
-     (the browser has a menu function for that)
-     However, often too much is found, and you may want to explicitely
-     exclude individual packages in the #excludedFromPreRequisites method."
+    "list packages which are mandatory as a prerequisite.
+     This are packages containing superclasses of my classes and classes which
+     are extended by myself.
+     They are mandatory, because we need these packages as a prerequisite for loading and compiling.
+     This method is generated automatically,
+     by searching along the inheritance chain of all of my classes."
 
     ^ #(
-        #'stx:libbasic'    "String - extended "
-        #'stx:libbasic3'    "VersionInfo - extended "
-        #'stx:libtool'    "Tools::NewSystemBrowser - extended "
-        #'stx:libview2'    "ApplicationModel - superclass of extended Tools::NewSystemBrowser "
-        #'stx:libcompat'
+        #'stx:libbasic'    "AbstractTime - extended"
+        #'stx:libbasic3'    "AbstractSourceCodeManager - superclass of MCSourceCodeManager"
+        #'stx:libcompat'    "ListItemWrapper - superclass of MCDependentsWrapper"
+        #'stx:libtool'    "AbstractSettingsApplication - superclass of MCSettingsApp"
+        #'stx:libview2'    "ApplicationModel - extended"
+        #'stx:libwidg2'    "AbstractHierarchicalItem - superclass of MCPackageEntry"
     )
 !
 
 referencedPreRequisites
-    "list all packages containing classes referenced by the packages's members.
-     This list can be maintained manually or (better) generated and
-     updated by looking for global variable accesses
-     (the browser has a menu function for that)
-     However, often too much is found, and you may want to explicitely
-     exclude individual packages in the #excludedFromPreRequisites method."
+    "list packages which are a prerequisite, because they contain
+     classes which are referenced by my classes.
+     We do not need these packages as a prerequisite for compiling or loading,
+     however, a class from it may be referenced during execution and having it
+     unloaded then may lead to a runtime doesNotUnderstand error, unless the caller
+     includes explicit checks for the package being present.
+     This method is generated automatically,
+     by searching all classes (and their packages) which are referenced by my classes."
 
     ^ #(
-        'stx:goodies/communication'     "/ HTTPInterface
+        #'stx:goodies/communication'    "FTPClient - referenced by MCFtpRepository>>clientDo:"
+        #'stx:libbasic2'    "Iterator - referenced by MCPackageList>>makeGenerator"
+        #'stx:libcomp'    "Parser - referenced by MCRepositoryBrowser>>repositoryAddFromExpressionString"
+        #'stx:libhtml'    "HTMLDocumentView - referenced by MCRepositoryBrowser>>openDocumentation"
+        #'stx:libscm/mercurial'    "HGChangesetDialog - referenced by MCRepositoryBrowser>>versionUpdateSplicemap"
+        #'stx:libview'    "Color - referenced by MCCommitDialog>>findUniqueVersionNumber"
+        #'stx:libwidg'    "PopUpMenu - referenced by MCVersionInspector>>pickAncestor"
+    )
+!
+
+subProjects
+    "list packages which are known as subprojects.
+     The generated makefile will enter those and make there as well.
+     However: they are not forced to be loaded when a package is loaded;
+     for those, redefine requiredPrerequisites."
+
+    ^ #(
     )
 ! !
 
@@ -114,6 +131,7 @@
         MCScanner
         MCSettingsApp
         MCSnapshot
+        MCSnapshotOptions
         MCSourceCodeManager
         MCStXNamespaceQuery
         MCStXPackageInfo
@@ -208,13 +226,14 @@
         (MCChangeSelector autoload)
         MCMcdReader
         (MCMergeBrowser autoload)
+        MCStXMczReader
         MCSubDirectoryRepository
     )
 !
 
 extensionMethodNames
-    "lists the extension methods which are to be included in the project.
-     Entries are pairwise elements, consisting of class-name and selector."
+    "list class/selector pairs of extensions.
+     A correponding method with real names must be present in my concrete subclasses"
 
     ^ #(
         Behavior traitCompositionString
@@ -250,6 +269,9 @@
         CharacterArray asStringWithSqueakLineEndings
         CharacterArray asStringWithNativeLineEndings
         'ProjectDefinition class' monticelloNameForMCZ
+        'ProjectDefinition class' monticelloSplicemap
+        'ProjectDefinition class' #'monticelloSplicemap_code'
+        'ProjectDefinition class' #'monticelloSplicemap_codeFor:'
     )
 ! !
 
@@ -305,5 +327,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> $'
 ! !
 
--- a/vcmake.bat	Thu Nov 03 13:22:28 2016 +0100
+++ b/vcmake.bat	Thu Nov 24 21:56:31 2016 +0000
@@ -10,11 +10,8 @@
     popd
 )
 @SET DEFINES=
-@REM Kludge got Mercurial, cannot be implemented in Borland make
-@FOR /F "tokens=*" %%i in ('hg root') do SET HGROOT=%%i
-@IF "%HGROOT%" NEQ "" SET DEFINES=%DEFINES% "-DHGROOT=%HGROOT%"
+
 make.exe -N -f bc.mak -DUSEVC=1 %DEFINES% %*
 
 
 
-