Fixes for mergetool jv
authorJan Vrany <jan.vrany@fit.cvut.cz>
Tue, 20 Mar 2012 16:55:14 +0000
branchjv
changeset 3033 8964521a2c1b
parent 3032 f8b04203694b
child 3034 c892671f3e2a
Fixes for mergetool
ChangeSet.st
ChangeSetDiffComponent.st
ChangeSetDiffEntry.st
ClassDefinitionChange.st
--- a/ChangeSet.st	Tue Mar 20 12:34:31 2012 +0000
+++ b/ChangeSet.st	Tue Mar 20 16:55:14 2012 +0000
@@ -35,7 +35,8 @@
 !
 
 SmalltalkChunkFileSourceWriter subclass:#ClassSourceWriter
-	instanceVariableNames:'changeSetBeingSaved infos topClassName classInfos metaInfos'
+	instanceVariableNames:'changeSetBeingSaved namespaceName topClassName classInfos
+		metaInfos'
 	classVariableNames:''
 	poolDictionaries:''
 	privateIn:ChangeSet
@@ -1698,8 +1699,6 @@
 
         anyFound ifFalse:[
             onlyInReceiver add:aChangeInA.
-        ] ifTrue:[
-            same add: aChangeInA.
         ]
     ].
 
@@ -1775,6 +1774,8 @@
                         Array with:cA with:cB
                       ].
 
+    same := self reject:[:chg|(changedMethods contains:[:pair|pair first == chg]) or:[onlyInReceiver includes: chg]].
+
     ret := DiffSet new
                 changed:changedMethods
                 onlyInReceiver:onlyInReceiver
@@ -1785,7 +1786,7 @@
 
     "Modified: / 12-10-2006 / 22:22:39 / cg"
     "Modified (comment): / 01-12-2011 / 19:12:55 / cg"
-    "Modified: / 19-03-2012 / 21:36:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 20-03-2012 / 14:13:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 diffSetsAgainstImage
@@ -1972,14 +1973,20 @@
     ].
 
     formatSymbolOrNil == #classSource ifTrue:[
-        ClassSourceWriter new fileOut: self on: aStream.
+        ClassSourceWriter new 
+            fileOut:self 
+            on:aStream 
+            withTimeStamp:false 
+            withInitialize:true 
+            withDefinition:true
+            methodFilter:nil encoder:nil.
         ^self.
     ].
 
     self error:'Unknown format, possible formats are { nil, #classSource }'
 
     "Created: / 08-02-2011 / 11:25:16 / cg"
-    "Modified: / 19-03-2012 / 17:22:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 20-03-2012 / 14:06:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !ChangeSet::ChangeFileReader methodsFor:'accessing'!
@@ -2702,7 +2709,7 @@
     "Pass 1 - collect classes"
     changeSetBeingSaved do:[:change|
         change isClassDefinitionChange ifTrue:[
-            | nm |
+            | nm ns |
 
             nm := change className.
             (nm endsWith:' class') ifFalse:[
@@ -2715,10 +2722,20 @@
                 change isPrivateClassDefinitionChange ifFalse:[
                     topClassName notNil ifTrue:[
                         self error: ('Multiple top class definitions (%1 vs %2)' bindWith: topClassName with: nm).
+                        ^self.
                     ].
                     topClassName := nm.
                 ]
             ].
+            ns := change nameSpaceName.
+            ns notNil ifTrue:[
+                (namespaceName notNil and:[namespaceName ~= ns]) ifTrue:[
+                    self error:('Multiple namespaces (%1 vs %2)' bindWith: namespaceName with: ns).
+                    ^self.
+                ] ifFalse:[
+                    namespaceName := ns.
+                ]
+            ].
         ]
     ].
 
@@ -3000,12 +3017,15 @@
     nonMetaInfo definition isPrivateClassDefinitionChange ifFalse:[
         nonMetaInfo definition package notNil ifTrue:[
             aStream nextPutAll: ('"{ Package: ''%1'' }"' bindWith: nonMetaInfo definition package).
-            aStream cr.
+            aStream cr; cr.
+        ].
+        namespaceName notNil ifTrue:[
+            aStream nextPutAll: ('"{ NameSpace: %1 }"' bindWith: namespaceName).
+            aStream cr; cr.
         ].
     ].
 
-
-    aStream nextPutAll: nonMetaInfo definition source.
+    aStream nextPutAll: nonMetaInfo definition definitionStringWithoutNamespace.
     aStream nextPutChunkSeparator. 
     aStream cr; cr.
 
@@ -3014,7 +3034,7 @@
     "/
     metaInfo := metaInfos at: nonMetaInfo name.
     metaInfo definition notNil ifTrue:[
-        aStream nextPutAll: metaInfo definition source.
+        aStream nextPutAll: metaInfo definition definitionStringWithoutNamespace.
         aStream nextPutChunkSeparator. 
         aStream cr; cr
     ].
@@ -3221,8 +3241,20 @@
 
 !ChangeSet::ClassSourceWriter::ClassInfo methodsFor:'printing & storing'!
 
-printClassNameOn:aStream    
-    aStream nextPutAll: name
+printClassNameOn:aStream
+    | nameWithoutNs i |
+
+    nameWithoutNs := name.
+    i := nameWithoutNs indexOf: $:.
+    i ~~ 0 ifTrue:[
+        self assert: (nameWithoutNs at: i + 1) == $:.
+        nameWithoutNs := nameWithoutNs copyFrom: i + 2.
+    ].
+    definition notNil ifTrue:[
+        self assert: nameWithoutNs = definition classNameWithoutNamespace
+    ].
+
+    aStream nextPutAll: nameWithoutNs
 
     "Created: / 19-03-2012 / 18:17:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
@@ -3667,5 +3699,5 @@
 !
 
 version_SVN
-    ^ '$Id: ChangeSet.st 1898 2012-03-20 12:34:31Z vranyj1 $'
+    ^ '$Id: ChangeSet.st 1899 2012-03-20 16:55:14Z vranyj1 $'
 ! !
--- a/ChangeSetDiffComponent.st	Tue Mar 20 12:34:31 2012 +0000
+++ b/ChangeSetDiffComponent.st	Tue Mar 20 16:55:14 2012 +0000
@@ -73,24 +73,58 @@
 
     cs := ChangeSet new name: self versionALabel.
     self do:[:item|
-        cs add: item versionA
+        (item versionMerged isClassDefinitionChange or:[item versionMerged isMethodCodeChange]) ifTrue:[
+            cs add: item versionA
+        ]
     ].
     ^cs
 
-    "Modified: / 16-12-2011 / 14:35:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 20-03-2012 / 13:57:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 changesetB
-    "Answers a changeset with containing all versionB changes"
+    "Answers a changeset with containing all versionA changes"
     | cs |
 
     cs := ChangeSet new name: self versionBLabel.
     self do:[:item|
-        cs add: item versionB
+        (item versionMerged isClassDefinitionChange or:[item versionMerged isMethodCodeChange]) ifTrue:[
+            cs add: item versionB
+        ]
     ].
     ^cs
 
-    "Modified: / 16-12-2011 / 14:35:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 20-03-2012 / 13:57:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+changesetBase
+    "Answers a changeset with containing all versionA changes"
+    | cs |
+
+    cs := ChangeSet new name: self versionBaseLabel.
+    self do:[:item|
+        (item versionBase isClassDefinitionChange or:[item versionBase isMethodCodeChange]) ifTrue:[
+            cs add: item versionBase
+        ]
+    ].
+    ^cs
+
+    "Created: / 20-03-2012 / 13:31:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+changesetMerged
+    "Answers a changeset with containing all versionA changes"
+    | cs |
+
+    cs := ChangeSet new name: 'Merged'.
+    self do:[:item|
+        (item versionMerged isClassDefinitionChange or:[item versionMerged isMethodCodeChange]) ifTrue:[
+            cs add: item versionMerged
+        ]
+    ].
+    ^cs
+
+    "Created: / 20-03-2012 / 13:32:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 diffs
@@ -107,12 +141,6 @@
     "Created: / 05-12-2009 / 11:07:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
-merged
-    "raise an error: must be redefined in concrete subclass(es)"
-
-    ^ self subclassResponsibility
-!
-
 name
     "raise an error: must be redefined in concrete subclass(es)"
 
@@ -137,6 +165,12 @@
     ^ parent versionBLabel
 
     "Created: / 09-11-2009 / 12:38:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+versionBaseLabel
+    ^ parent versionBaseLabel
+
+    "Created: / 20-03-2012 / 13:31:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !ChangeSetDiffComponent methodsFor:'change & update'!
@@ -209,5 +243,5 @@
 !
 
 version_SVN
-    ^ '$Id: ChangeSetDiffComponent.st 1896 2012-03-19 15:30:00Z vranyj1 $'
+    ^ '$Id: ChangeSetDiffComponent.st 1899 2012-03-20 16:55:14Z vranyj1 $'
 ! !
--- a/ChangeSetDiffEntry.st	Tue Mar 20 12:34:31 2012 +0000
+++ b/ChangeSetDiffEntry.st	Tue Mar 20 16:55:14 2012 +0000
@@ -151,12 +151,6 @@
     "Created: / 19-03-2012 / 14:57:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
-merged
-    ^ versionMerged notNil
-
-    "Modified: / 24-11-2009 / 12:55:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
 mergedUsingVersionA
 
     versionMerged ifNil:[^false].
@@ -258,12 +252,6 @@
     versionBase := something.
 !
 
-versionBaseLabel
-    ^ parent versionBaseLabel
-
-    "Created: / 23-11-2009 / 22:55:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
 versionBaseText
     ^versionBase notNil ifTrue:[
         versionBase source
@@ -275,7 +263,17 @@
 !
 
 versionMerged
-    ^ versionMerged
+    "Returns a change representing a merge"
+
+    | merged |
+    merged := versionMerged.
+    (merged isNil and:[mergeInfo notNil]) ifTrue:[
+        merged := (versionA ? versionB ? versionBase) copy.
+        merged source: mergeInfo text.
+    ].
+    ^merged
+
+    "Modified: / 20-03-2012 / 14:38:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 versionMerged:aChange
@@ -335,6 +333,8 @@
 isMerged
     | mi |
 
+    versionMerged notNil ifTrue:[ ^ true ].
+
     ^(mi := self mergeInfo) notNil ifTrue:[
         mi isMerged
     ] ifFalse:[
@@ -351,5 +351,5 @@
 !
 
 version_SVN
-    ^ '$Id: ChangeSetDiffEntry.st 1896 2012-03-19 15:30:00Z vranyj1 $'
+    ^ '$Id: ChangeSetDiffEntry.st 1899 2012-03-20 16:55:14Z vranyj1 $'
 ! !
--- a/ClassDefinitionChange.st	Tue Mar 20 12:34:31 2012 +0000
+++ b/ClassDefinitionChange.st	Tue Mar 20 16:55:14 2012 +0000
@@ -418,6 +418,88 @@
     "Modified: / 19-03-2012 / 19:19:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
+definitionStringWithoutNamespace
+    |ns classNameUsed superClassNameUsed|
+
+    ns := self nameSpaceOverride.
+
+    objectType == #variable ifTrue:[
+        ^ String streamContents:[:stream |
+            ns notNil ifTrue:[
+                stream 
+                    nextPutAll:((ns asCollectionOfSubstringsSeparatedBy:$.) asStringWith:'::')
+            ] ifFalse:[
+                self halt:'can this happen ?'.
+                stream 
+                    nextPutAll:'Smalltalk'
+            ].
+
+            stream 
+                nextPutAll:' addClassVarName:';
+                nextPutAll:className asString storeString
+          ].
+    ].
+
+    superClassNameUsed := self superClassName.
+    classNameUsed := self classNameWithoutNamespace.
+
+    ^ String streamContents:[:stream |
+        self isPrivateClassDefinitionChange ifFalse:[
+            stream 
+                nextPutAll:superClassNameUsed;
+                nextPutAll:' subclass:';
+                nextPutAll: classNameUsed asSymbol storeString
+                ;
+                cr;
+                tab;
+                nextPutAll:'instanceVariableNames:';
+                nextPutAll:(instanceVariableNames ? '') storeString;
+                cr;
+                tab;
+                nextPutAll:'classVariableNames:';
+                nextPutAll:(classVariableNames ? '') storeString;
+                cr;
+                tab;
+                nextPutAll:'poolDictionaries:';
+                nextPutAll:(poolDictionaries ? '') storeString;
+                cr;
+                tab;
+                nextPutAll:'category:';
+                nextPutAll:(category ? '') storeString;
+                cr
+        ] ifTrue:[
+            stream 
+                nextPutAll:superClassNameUsed;
+                nextPutAll:' subclass:';
+                nextPutAll: (self className copyFrom: owningClassName size + 3) asSymbol storeString
+                ;
+                cr;
+                tab;
+                nextPutAll:'instanceVariableNames:';
+                nextPutAll:(instanceVariableNames ? '') storeString;
+                cr;
+                tab;
+                nextPutAll:'classVariableNames:';
+                nextPutAll:(classVariableNames ? '') storeString;
+                cr;
+                tab;
+                nextPutAll:'poolDictionaries:';
+                nextPutAll:(poolDictionaries ? '') storeString;
+                cr;
+                tab;
+                nextPutAll:'privateIn:';
+                nextPutAll:
+                    ((ns := self nameSpaceName) isNil
+                        ifTrue:[owningClassName]
+                        ifFalse:[owningClassName copyFrom: ns size + 3]);
+                cr
+        ]
+    ]
+
+    "Modified: / 06-10-2011 / 17:02:05 / cg"
+    "Created: / 20-03-2012 / 16:37:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 printOn:aStream
     aStream 
         nextPutAll:className; nextPutAll:' {definition}'
@@ -596,7 +678,7 @@
 !ClassDefinitionChange class methodsFor:'documentation'!
 
 version
-    ^ '$Id: ClassDefinitionChange.st 1897 2012-03-19 20:13:30Z vranyj1 $'
+    ^ '$Id: ClassDefinitionChange.st 1899 2012-03-20 16:55:14Z vranyj1 $'
 !
 
 version_CVS
@@ -604,5 +686,5 @@
 !
 
 version_SVN
-    ^ '$Id: ClassDefinitionChange.st 1897 2012-03-19 20:13:30Z vranyj1 $'
+    ^ '$Id: ClassDefinitionChange.st 1899 2012-03-20 16:55:14Z vranyj1 $'
 ! !