Improvements in merge tool jv
authorJan Vrany <jan.vrany@fit.cvut.cz>
Wed, 21 Mar 2012 01:52:35 +0000
branchjv
changeset 12202 eaa1f6cb6ce8
parent 12201 283826cb8bcc
child 12203 bcfd4488d8a2
Improvements in merge tool
Diff3.st
Diff3Hunk.st
Tools__ChangeSetDiffList.st
Tools__ChangeSetDiffTool.st
Tools__Diff3CodeView2.st
Tools__TextDiff3Tool.st
Tools__TextMergeInfo.st
stx_libtool.st
--- a/Diff3.st	Tue Mar 20 16:59:54 2012 +0000
+++ b/Diff3.st	Wed Mar 21 01:52:35 2012 +0000
@@ -148,6 +148,48 @@
 
 !Diff3 methodsFor:'merging'!
 
+diffIndices
+    "Returns an Array of Diff3Chunks (representing clean merges) or Diff3Conflicts 
+     (containing DiffChunks, representing conflicts), together representing the 
+     results of a three-way merge between file1/file0/file2. Does not detect 
+     'false conflicts', and can return two Diff3Chunks next to each other in 
+     the result."
+
+    | result commonOffset hunks lastOverlapHunkIndex hunk firstHunkIndex |
+
+    hunks := self computeHunks.
+    result := OrderedCollection new.
+    commonOffset := 1.
+    firstHunkIndex := 1.
+    [firstHunkIndex <= hunks size] whileTrue: [
+
+        hunk := hunks at: firstHunkIndex.
+        self addCommonChunkTo: result between: commonOffset and: hunk oldChunk offset.
+        lastOverlapHunkIndex := self findOverlapStartingAt: firstHunkIndex in: hunks.
+
+        "(firstHunkIndex = lastOverlapHunkIndex)"false ifTrue: [
+            (hunk newChunk length > 0) ifTrue: [
+                result add: (Diff3::Chunk side: hunk side chunk: hunk newChunk)
+            ].
+            commonOffset := (hunks at: lastOverlapHunkIndex) oldChunk lastIndex + 1.
+        ] ifFalse: [ 
+            | conflict |
+            conflict := self computeConflictFrom: firstHunkIndex
+                                            to: lastOverlapHunkIndex
+                                            hunks: hunks.
+            result add: conflict.
+            commonOffset := conflict original lastIndex + 1.
+        ].
+
+        firstHunkIndex := lastOverlapHunkIndex + 1
+    ].
+    self addCommonChunkTo: result between: commonOffset and: file0 size + 1.
+    ^ result asArray
+
+    "Modified: / 16-03-2012 / 19:24:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Created: / 20-03-2012 / 18:27:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 merge
     "Returns an Array of (#ok -> {...}) or (#conflict -> Diff3Conflict 
      of collections) instances representing the results of a three-way 
@@ -172,32 +214,45 @@
 !
 
 mergeIndices
-        "Returns an Array of Diff3Chunks (representing clean merges) or Diff3Conflicts (containing DiffChunks, representing conflicts), together representing the results of a three-way merge between file1/file0/file2. Does not detect 'false conflicts', and can return two Diff3Chunks next to each other in the result."
-        | result commonOffset hunks lastOverlapHunkIndex hunk firstHunkIndex |
-        hunks := self computeHunks.
-        result := OrderedCollection new.
-        commonOffset := 1.
-        firstHunkIndex := 1.
-        [firstHunkIndex <= hunks size] whileTrue: [
-                hunk := hunks at: firstHunkIndex.
-                self addCommonChunkTo: result between: commonOffset and: hunk oldChunk offset.
-                lastOverlapHunkIndex := self findOverlapStartingAt: firstHunkIndex in: hunks.
-                (firstHunkIndex = lastOverlapHunkIndex)
-                        ifTrue: [
-                                (hunk newChunk length > 0)
-                                        ifTrue: [result add: (Diff3::Chunk side: hunk side chunk: hunk newChunk)].
-                                commonOffset := (hunks at: lastOverlapHunkIndex) oldChunk lastIndex + 1.]
-                        ifFalse: [ | conflict |
-                                conflict := self computeConflictFrom: firstHunkIndex
-                                                                to: lastOverlapHunkIndex
-                                                                hunks: hunks.
-                                result add: conflict.
-                                commonOffset := conflict original lastIndex + 1.].
-                firstHunkIndex := lastOverlapHunkIndex + 1].
-        self addCommonChunkTo: result between: commonOffset and: file0 size + 1.
-        ^ result asArray
+    "Returns an Array of Diff3Chunks (representing clean merges) or Diff3Conflicts 
+     (containing DiffChunks, representing conflicts), together representing the 
+     results of a three-way merge between file1/file0/file2. Does not detect 
+     'false conflicts', and can return two Diff3Chunks next to each other in 
+     the result."
+
+    | result commonOffset hunks lastOverlapHunkIndex hunk firstHunkIndex |
+
+    hunks := self computeHunks.
+    result := OrderedCollection new.
+    commonOffset := 1.
+    firstHunkIndex := 1.
+    [firstHunkIndex <= hunks size] whileTrue: [
+
+        hunk := hunks at: firstHunkIndex.
+        self addCommonChunkTo: result between: commonOffset and: hunk oldChunk offset.
+        lastOverlapHunkIndex := self findOverlapStartingAt: firstHunkIndex in: hunks.
+
+        (firstHunkIndex = lastOverlapHunkIndex) ifTrue: [
+            (hunk newChunk length > 0) ifTrue: [
+                result add: (Diff3::Chunk side: hunk side chunk: hunk newChunk)
+            ].
+            commonOffset := (hunks at: lastOverlapHunkIndex) oldChunk lastIndex + 1.
+        ] ifFalse: [ 
+            | conflict |
+            conflict := self computeConflictFrom: firstHunkIndex
+                                            to: lastOverlapHunkIndex
+                                            hunks: hunks.
+            result add: conflict.
+            commonOffset := conflict original lastIndex + 1.
+        ].
+
+        firstHunkIndex := lastOverlapHunkIndex + 1
+    ].
+    self addCommonChunkTo: result between: commonOffset and: file0 size + 1.
+    ^ result asArray
 
     "Modified: / 16-03-2012 / 19:24:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified (format): / 20-03-2012 / 18:07:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !Diff3 methodsFor:'private'!
@@ -261,13 +316,18 @@
 !
 
 findOverlapStartingAt: startIndex in: hunks
-	| nextRegionLhs hunk |
-	nextRegionLhs := (hunks at: startIndex) oldChunk lastIndex + 1.
-	startIndex + 1 to: hunks size do: [:index |
-		hunk := hunks at: index.
-		hunk oldChunk offset > nextRegionLhs ifTrue: [^ index - 1].
-		nextRegionLhs := nextRegionLhs max: hunk oldChunk lastIndex + 1].
-	^ hunks size.
+        | nextRegionLhs hunk |
+        nextRegionLhs := (hunks at: startIndex) oldChunk lastIndex + 1.
+        startIndex + 1 to: hunks size do: [:index |
+                hunk := hunks at: index.
+                hunk oldChunk offset > nextRegionLhs ifTrue: [ 
+                    ^ index - 1
+                ].
+                nextRegionLhs := nextRegionLhs max: hunk oldChunk lastIndex + 1
+        ].
+        ^ hunks size.
+
+    "Modified (format): / 20-03-2012 / 18:04:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 merge: excludeFalseConflicts
@@ -417,12 +477,20 @@
 !
 
 printOn: aStream
-	aStream nextPut: $(.
-	super printOn: aStream.
-	aStream
-		nextPutAll: ' side: ';
-		nextPutAll: side printString;
-		nextPut: $).
+        aStream nextPut: $(.
+        super printOn: aStream.
+        aStream
+                nextPutAll: ' side: ';
+                nextPutAll: side printString;
+                nextPutAll: ' off: ';
+                nextPutAll: offset printString;
+                nextPutAll: ' len: ';
+                nextPutAll: length printString;
+
+
+                nextPut: $).
+
+    "Modified: / 20-03-2012 / 17:08:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !Diff3::Chunk methodsFor:'comparing'!
@@ -512,6 +580,17 @@
 	left := anObject
 !
 
+leftAt: index
+
+    ^(index between: 1 and: left size) ifTrue:[
+        left at: index
+    ] ifFalse:[
+        nil
+    ]
+
+    "Created: / 20-03-2012 / 20:48:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 length
 
     ^left length max: (original length max: right length)
@@ -527,12 +606,34 @@
 	original := anObject
 !
 
+originalAt: index
+
+    ^(index between: 1 and: original size) ifTrue:[
+        original at: index
+    ] ifFalse:[
+        nil
+    ]
+
+    "Created: / 20-03-2012 / 20:49:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 right
 	^ right
 !
 
 right: anObject
 	right := anObject
+!
+
+rightAt: index
+
+    ^(index between: 1 and: right size) ifTrue:[
+        right at: index
+    ] ifFalse:[
+        nil
+    ]
+
+    "Created: / 20-03-2012 / 20:48:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !Diff3::Conflict methodsFor:'as yet unclassified'!
@@ -575,10 +676,34 @@
     ^true
 
     "Created: / 16-03-2012 / 22:03:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+isInsertionInLeft
+    ^left length > 0
+        and:[original length <= 0
+            and:[right length <= 0]]
+
+    "Created: / 20-03-2012 / 18:37:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+isInsertionInOriginal
+    ^original length > 0
+        and:[left length <= 0
+            and:[right length <= 0]]
+
+    "Created: / 20-03-2012 / 18:36:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+isInsertionInRight
+    ^right length > 0
+        and:[original length <= 0
+            and:[left length <= 0]]
+
+    "Created: / 20-03-2012 / 18:37:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !Diff3 class methodsFor:'documentation'!
 
 version_SVN
-    ^ '$Id: Diff3.st 7936 2012-03-16 22:44:50Z vranyj1 $'
+    ^ '$Id: Diff3.st 7948 2012-03-21 01:52:35Z vranyj1 $'
 ! !
--- a/Diff3Hunk.st	Tue Mar 20 16:59:54 2012 +0000
+++ b/Diff3Hunk.st	Wed Mar 21 01:52:35 2012 +0000
@@ -134,8 +134,24 @@
 		[(otherHunk oldChunk = oldChunk) and: [side = #left]]
 ! !
 
+!Diff3Hunk methodsFor:'printing & storing'!
+
+printOn:aStream
+    "append a printed representation if the receiver to the argument, aStream"
+
+    super printOn:aStream.
+    aStream nextPutAll:' side: '.
+    side printOn:aStream.
+    aStream nextPutAll:' old: '.
+    oldChunk printOn:aStream.
+    aStream nextPutAll:' new: '.
+    newChunk printOn:aStream.
+
+    "Modified: / 20-03-2012 / 17:56:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
 !Diff3Hunk class methodsFor:'documentation'!
 
 version_SVN
-    ^ '$Id: Diff3Hunk.st 7927 2012-03-16 19:30:50Z vranyj1 $'
+    ^ '$Id: Diff3Hunk.st 7948 2012-03-21 01:52:35Z vranyj1 $'
 ! !
--- a/Tools__ChangeSetDiffList.st	Tue Mar 20 16:59:54 2012 +0000
+++ b/Tools__ChangeSetDiffList.st	Wed Mar 21 01:52:35 2012 +0000
@@ -341,15 +341,17 @@
 
 displayOn: aGC x: x y: y opaque: opaque
 
-    | icon oldPaint  |
+    | label icon oldPaint |
+    label := self label.
     ((application topApplication askFor:#isMerge) and:[model isMerged not]) ifTrue:[
         oldPaint := aGC paint.
         aGC paint: TextDiff3Tool colorConflict.
         '!!' displayOn: aGC x: x  y:y opaque: opaque.
         aGC paint: oldPaint.
+        label := label asText allBold"/ colorizeAllWith: Color red darker
     ].
     (icon := self icon) ifNotNil:[icon displayOn: aGC x: x + 10 y: y - icon height opaque: opaque].
-    self label displayOn: aGC x: x + 10 + 16 y:y opaque: opaque
+    label displayOn: aGC x: x + 10 + 16 y:y opaque: opaque
 
     "Created: / 24-11-2009 / 18:21:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
@@ -361,5 +363,5 @@
 !
 
 version_SVN
-    ^ '$Id: Tools__ChangeSetDiffList.st 7944 2012-03-19 15:32:45Z vranyj1 $'
+    ^ '$Id: Tools__ChangeSetDiffList.st 7948 2012-03-21 01:52:35Z vranyj1 $'
 ! !
--- a/Tools__ChangeSetDiffTool.st	Tue Mar 20 16:59:54 2012 +0000
+++ b/Tools__ChangeSetDiffTool.st	Wed Mar 21 01:52:35 2012 +0000
@@ -714,6 +714,7 @@
                   label: 'Exit'
                   itemValue: closeRequest
                   translateLabel: true
+                  shortcutKey: Ctrlq
                 )
                )
               nil
@@ -1340,12 +1341,12 @@
     self diffInfo isNil ifTrue:[ ^ self ].
 
     self diffInfo isDiff3 ifTrue:[
-        textDiffToolHolder value isDiff3 ifFalse:[
+        self textDiffToolHolder value isDiff3 ifFalse:[
             textDiffToolHolder value: self textDiff3Tool.
         ].
         self mergeHolder value: self diffInfo isMerge.
     ] ifFalse:[
-        textDiffToolHolder value isDiff2 ifFalse:[
+        self textDiffToolHolder value isDiff2 ifFalse:[
             textDiffToolHolder value: self textDiff2Tool.
         ].
         self mergeHolder value: false.
@@ -2450,5 +2451,5 @@
 !
 
 version_SVN
-    ^ '$Id: Tools__ChangeSetDiffTool.st 7947 2012-03-20 16:59:54Z vranyj1 $'
+    ^ '$Id: Tools__ChangeSetDiffTool.st 7948 2012-03-21 01:52:35Z vranyj1 $'
 ! !
--- a/Tools__Diff3CodeView2.st	Tue Mar 20 16:59:54 2012 +0000
+++ b/Tools__Diff3CodeView2.st	Wed Mar 21 01:52:35 2012 +0000
@@ -186,16 +186,20 @@
 addLines: total from: src to: dst offset: offset length: len
     | start stop |
 
-    start := offset.
-    stop  := (offset + len - 1).
+    start := offset max:1.
+    stop  := (offset + (len max:0) - 1).
 
 
-    start to: stop do:[:i|                     
-        dst add: (src at: i).
+    start to: (stop min: src size) do:[:i|                     
+        (src size >= i) ifTrue:[
+            dst add: (src at: i).
+        ] ifFalse:[
+            src add: nil.
+        ]
     ].
 
 
-    (total - (stop - start + 1)) timesRepeat: [ dst add: nil ].
+    (total - ((stop min: src size) - start + 1)) timesRepeat: [ dst add: nil ].
 
     "Created: / 16-03-2012 / 22:20:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
@@ -211,6 +215,78 @@
     inserted2 := OrderedCollection new.
     inserted3 := OrderedCollection new.
 
+"/    t1 isNil ifTrue:[ ^self ].
+"/    t2 isNil ifTrue:[ ^self ].
+"/    t3 isNil ifTrue:[ ^self ].
+
+
+    t1c := (text1 := t1 ? #()) asStringCollection.
+    t2c := (text2 := t2 ? #()) asStringCollection.
+    t3c := (text3 := t3 ? #()) asStringCollection.
+
+    
+    diff3chunks := Diff3 new
+                    file0: t1c; "/Base version
+                    file1: t2c; "/A
+                    file2: t3c; "/B
+                    diffIndices.
+    lnr := 1.
+    diff3chunks do:[:chunk|
+        | len |
+
+        len := chunk length.
+        chunk isConflict ifTrue:[
+            self addLines: len from: t1c to: list1 offset: chunk original offset length: chunk original length.
+            self addLines: len from: t2c to: list2 offset: chunk left     offset length: chunk left     length.
+            self addLines: len from: t3c to: list3 offset: chunk right    offset length: chunk right    length.
+            chunk isInsertionInOriginal ifTrue:[
+                lnr to:(lnr + len -1) do:[:i|inserted1 add: i].
+            ] ifFalse:[chunk isInsertionInLeft ifTrue:[
+                lnr to:(lnr + len -1) do:[:i|inserted2 add: i].
+            ] ifFalse:[chunk isInsertionInRight ifTrue:[
+                lnr to:(lnr + len -1) do:[:i|inserted3 add: i].
+            ] ifFalse:[
+                lnr to:(lnr + len -1) do:[:i|changed add: i].
+            ]]]
+        ].
+        chunk isChunk ifTrue:[
+            chunk side == #original ifTrue:[
+                self addLines: len from: t1c to: list1 offset: chunk offset length: len.
+                self addLines: len from: t1c to: list2 offset: chunk offset length: len.
+                self addLines: len from: t1c to: list3 offset: chunk offset length: len.
+            ].
+            chunk side == #left ifTrue:[
+                self breakPoint: #jv info: 'Should no longer happen'.
+                self addLines: len from: t1c to: list1 offset: chunk offset length: 0"len".
+                self addLines: len from: t2c to: list2 offset: chunk offset length: len.
+                self addLines: len from: t3c to: list3 offset: chunk offset length: 0"len".
+                lnr to:(lnr + len - 1) do:[:i| "changed"inserted2 add:i ].
+            ].
+            chunk side == #right ifTrue:[
+                self breakPoint: #jv info: 'Should no longer happen'.
+                self addLines: len from: t1c to: list1 offset: chunk offset length: 0"len".
+                self addLines: len from: t2c to: list2 offset: chunk offset length: 0"len".
+                self addLines: len from: t3c to: list3 offset: chunk offset length: len.
+                lnr to:(lnr + len - 1) do:[:i|"changed"inserted3 add: i].
+            ]
+        ].
+        lnr := lnr + len.
+    ].
+
+    "Created: / 16-03-2012 / 22:07:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+old_computeDiffDataForText1:t1 text2:t2 text3: t3
+    | t1c t2c  t3c  diff3chunks lnr |
+
+    list1 := StringCollection new.
+    list2 := StringCollection new.
+    list3 := StringCollection new.
+    changed := OrderedCollection new.
+    inserted1 := OrderedCollection new.
+    inserted2 := OrderedCollection new.
+    inserted3 := OrderedCollection new.
+
     t1 isNil ifTrue:[ ^self ].
     t2 isNil ifTrue:[ ^self ].
     t3 isNil ifTrue:[ ^self ].
@@ -267,11 +343,11 @@
         lnr := lnr + len.
     ].
 
-    "Created: / 16-03-2012 / 22:07:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Created: / 20-03-2012 / 17:42:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !Diff3CodeView2 class methodsFor:'documentation'!
 
 version_SVN
-    ^ '$Id: Tools__Diff3CodeView2.st 7938 2012-03-17 10:21:50Z vranyj1 $'
+    ^ '$Id: Tools__Diff3CodeView2.st 7948 2012-03-21 01:52:35Z vranyj1 $'
 ! !
--- a/Tools__TextDiff3Tool.st	Tue Mar 20 16:59:54 2012 +0000
+++ b/Tools__TextDiff3Tool.st	Wed Mar 21 01:52:35 2012 +0000
@@ -407,7 +407,9 @@
 !TextDiff3Tool methodsFor:'actions'!
 
 doMergeAuto
-    self halt.
+
+    self mergeDataHolder value 
+        text1: self textC text2: self textA text3: self textB.
 
     "Created: / 17-03-2012 / 12:55:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
@@ -806,6 +808,19 @@
     "Created: / 19-03-2012 / 13:15:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+!TextDiff3Tool::MergeService methodsFor:'event handling'!
+
+linesModifiedFrom: start to: end
+
+    start to: end do:[:i|
+        (data listInfos at:i) resolution: #Merged.
+    ].
+    gutterView invalidate.
+
+    "Created: / 06-07-2011 / 17:14:36 / jv"
+    "Created: / 20-03-2012 / 22:57:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
 !TextDiff3Tool::MergeService methodsFor:'registering'!
 
 registerIn: aCodeView
@@ -822,5 +837,5 @@
 !TextDiff3Tool class methodsFor:'documentation'!
 
 version_SVN
-    ^ '$Id: Tools__TextDiff3Tool.st 7947 2012-03-20 16:59:54Z vranyj1 $'
+    ^ '$Id: Tools__TextDiff3Tool.st 7948 2012-03-21 01:52:35Z vranyj1 $'
 ! !
--- a/Tools__TextMergeInfo.st	Tue Mar 20 16:59:54 2012 +0000
+++ b/Tools__TextMergeInfo.st	Wed Mar 21 01:52:35 2012 +0000
@@ -21,7 +21,7 @@
 !
 
 Object subclass:#LineInfo
-	instanceVariableNames:'line resolution conflict'
+	instanceVariableNames:'line resolution conflict offset'
 	classVariableNames:''
 	poolDictionaries:''
 	privateIn:TextMergeInfo
@@ -54,7 +54,7 @@
 !
 
 text
-    ^list asString
+    ^(list reject:[:l|l isNil]) asString
 
     "Created: / 19-03-2012 / 14:58:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
@@ -68,14 +68,9 @@
     list := StringCollection new.
     listInfos := OrderedCollection new.
 
-    text1 isNil ifTrue:[ ^self ].
-    text2 isNil ifTrue:[ ^self ].
-    text2 isNil ifTrue:[ ^self ].
-
-
-    t1c := text1 asStringCollection.
-    t2c := text2 asStringCollection.
-    t3c := text3 asStringCollection.
+    t1c := (text1 ? #()) asStringCollection.
+    t2c := (text2 ? #()) asStringCollection.
+    t3c := (text3 ? #()) asStringCollection.
 
 
     merges := Diff3 new
@@ -93,9 +88,9 @@
             ].
         ].
         merge key == #conflict ifTrue:[
-            merge value length timesRepeat:[
+            1 to: merge value length do:[:i|
                 list add:nil. "/no resolution now"
-                listInfos add: (LineInfo line: lnr resolution: #Conflict conflict: merge value).
+                listInfos add: (LineInfo line: lnr resolution: #Conflict conflict: merge value offset: i).
                 lnr := lnr + 1.
             ].
         ].
@@ -117,7 +112,7 @@
 
         lineInfo := listInfos at: lineNr.
         lineInfo conflict notNil ifTrue:[
-            self list at: lineNr put: (lineInfo conflict left first).
+            self list at: lineNr put: (lineInfo conflict leftAt: lineInfo offset).
             lineInfo resolution: #MergedUsingA.
             changed := true
         ].
@@ -136,7 +131,7 @@
 
         lineInfo := listInfos at: lineNr.
         lineInfo conflict notNil ifTrue:[
-            self list at: lineNr put: (lineInfo conflict right first).
+            self list at: lineNr put: (lineInfo conflict rightAt: lineInfo offset).
             lineInfo resolution: #MergedUsingB.
             changed := true
         ].
@@ -158,7 +153,7 @@
 !TextMergeInfo::LineInfo class methodsFor:'accessing'!
 
 line:lineArg resolution:resolutionArg
-    ^self new line:lineArg resolution:resolutionArg conflict:nil
+    ^self new line:lineArg resolution:resolutionArg conflict:nil offset: nil
 
     "Created: / 19-03-2012 / 15:04:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
@@ -168,6 +163,14 @@
     ^self new line:lineArg resolution:resolutionArg conflict:conflictArg
 
     "Modified: / 19-03-2012 / 15:07:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+line:lineArg resolution:resolutionArg conflict:conflictArg offset: offsetArg 
+
+    ^self new line:lineArg resolution:resolutionArg conflict:conflictArg offset: offsetArg
+
+    "Modified: / 19-03-2012 / 15:07:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Created: / 20-03-2012 / 20:42:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !TextMergeInfo::LineInfo methodsFor:'accessing'!
@@ -194,15 +197,22 @@
 !
 
 line:lineArg resolution:resolutionArg
-    self line:lineArg resolution:resolutionArg conflict:nil
+    self line:lineArg resolution:resolutionArg conflict:nil offset: nil
 
     "Created: / 19-03-2012 / 15:04:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
-line:lineArg resolution:resolutionArg conflict:conflictArg 
+line:lineArg resolution:resolutionArg conflict:conflictArg offset: offsetArg
     line := lineArg.
     resolution := resolutionArg.
     conflict := conflictArg.
+    offset := offsetArg
+
+    "Created: / 20-03-2012 / 20:41:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+offset
+    ^ offset
 !
 
 resolution
@@ -273,5 +283,5 @@
 !TextMergeInfo class methodsFor:'documentation'!
 
 version_SVN
-    ^ '$Id: Tools__TextMergeInfo.st 7947 2012-03-20 16:59:54Z vranyj1 $'
+    ^ '$Id: Tools__TextMergeInfo.st 7948 2012-03-21 01:52:35Z vranyj1 $'
 ! !
--- a/stx_libtool.st	Tue Mar 20 16:59:54 2012 +0000
+++ b/stx_libtool.st	Wed Mar 21 01:52:35 2012 +0000
@@ -95,19 +95,19 @@
      exclude individual packages in the #excludedFromPrerequisites method."
 
     ^ #(
-        #'stx:goodies/refactoryBrowser/parser'    "RBProgramNodeVisitor - superclass of CodeGenerator "
-        #'stx:goodies/sunit'    "TestResult - referenced by Tools::TestRunner2>>debugError: "
-        #'stx:libbasic'    "Dictionary - superclass of extended IdentityDictionary "
-        #'stx:libbasic2'    "List - superclass of AbstractFileBrowser::DirectoryHistory "
+        #'stx:goodies/refactoryBrowser/parser'    "RBProgramNodeVisitor - superclass of Tools::BreakpointBrowser::MessageArgumentExtractor "
+        #'stx:goodies/sunit'    "TestResultForRunWithDebug - referenced by Tools::TestRunnerEmbedded>>runWithDebug "
+        #'stx:libbasic'    "ExecutableFunction - superclass of Tools::MethodCategoryList::MissingMethod "
+        #'stx:libbasic2'    "List - superclass of BookmarkList "
         #'stx:libbasic3'    "MessageTally - superclass of Tools::Profiler "
         #'stx:libboss'    "BinaryOutputManager - referenced by Tools::Profiler>>storeStatisticsOn: "
-        #'stx:libcomp'    "SyntaxHighlighter - superclass of SyntaxHighlighter2 "
-        #'stx:libhtml'    "HTMLParser - referenced by Tools::TagList>>htmlTagsInFile: "
+        #'stx:libcomp'    "Parser - superclass of SyntaxHighlighter2 "
+        #'stx:libhtml'    "HTMLDocumentView - referenced by AbstractFileBrowser>>openHTMLReader "
         #'stx:libui'    "ViewSpec - superclass of FileBrowserV2UISpecifications::PanelSpec "
-        #'stx:libview'    "ModalBox - superclass of AboutBox "
-        #'stx:libview2'    "ToolApplicationModel - superclass of AbstractLauncherApplication "
-        #'stx:libwidg'    "EditTextView - superclass of Tools::CodeView2::TextView "
-        #'stx:libwidg2'    "SyncedMultiColumnTextView - superclass of DiffTextView "
+        #'stx:libview'    "PopUpView - superclass of extended PopUpMenu "
+        #'stx:libview2'    "ToolApplicationModel - superclass of WorkspaceApplication "
+        #'stx:libwidg'    "VariablePanel - superclass of FileBrowserV2PanelView "
+        #'stx:libwidg2'    "TwoColumnTextView - superclass of DiffCodeView "
     )
 ! !
 
@@ -348,6 +348,7 @@
         Diff3ExclusiveVisitor
         #'Tools::TextMergeInfo'
         FileBrowserV3
+        #'Tools::ChangeSetDiffInfo'
     )
 !
 
@@ -473,6 +474,7 @@
         'GenericToolbarIconLibrary class' smalllintWarning16x16
         UnboxedIntegerArray inspector2TabForHexDump
         UnboxedIntegerArray inspector2Tabs
+        'GenericToolbarIconLibrary class' versionMerged24x24
     )
 ! !
 
@@ -525,13 +527,13 @@
     "Return a SVN revision number of myself.
      This number is updated after a commit"
 
-    ^ "$SVN-Revision:"'7943'"$"
+    ^ "$SVN-Revision:"'7946'"$"
 ! !
 
 !stx_libtool class methodsFor:'documentation'!
 
 version
-    ^ '$Id: stx_libtool.st 7945 2012-03-19 20:14:57Z vranyj1 $'
+    ^ '$Id: stx_libtool.st 7948 2012-03-21 01:52:35Z vranyj1 $'
 !
 
 version_CVS
@@ -539,5 +541,5 @@
 !
 
 version_SVN
-    ^ '$Id: stx_libtool.st 7945 2012-03-19 20:14:57Z vranyj1 $'
+    ^ '$Id: stx_libtool.st 7948 2012-03-21 01:52:35Z vranyj1 $'
 ! !