Diff3.st
branchjv
changeset 12225 60dfd3fa018d
parent 12218 8b88c30fb1e7
child 12226 4e263f50f1c6
equal deleted inserted replaced
12224:eabcf6fc3857 12225:60dfd3fa018d
   190     hunks := self computeHunks.
   190     hunks := self computeHunks.
   191     result := OrderedCollection new.
   191     result := OrderedCollection new.
   192     commonOffset := 1.
   192     commonOffset := 1.
   193     firstHunkIndex := 1.
   193     firstHunkIndex := 1.
   194     [firstHunkIndex <= hunks size] whileTrue: [
   194     [firstHunkIndex <= hunks size] whileTrue: [
       
   195         | conflict |
   195 
   196 
   196         hunk := hunks at: firstHunkIndex.
   197         hunk := hunks at: firstHunkIndex.
   197         self addCommonChunkTo: result between: commonOffset and: hunk oldChunk offset.
   198         self addCommonChunkTo: result between: commonOffset and: hunk oldChunk offset.
   198         lastOverlapHunkIndex := self findOverlapStartingAt: firstHunkIndex in: hunks.
   199         lastOverlapHunkIndex := self findOverlapStartingAt: firstHunkIndex in: hunks.
   199 
   200 
   200         "(firstHunkIndex = lastOverlapHunkIndex)"false ifTrue: [
   201         (firstHunkIndex = lastOverlapHunkIndex)"false" ifTrue: [
   201             (hunk newChunk length > 0) ifTrue: [
   202             conflict := self computeConflictFromCleanMerge: hunk.
   202                 result add: (Diff3::Chunk side: hunk side chunk: hunk newChunk)
   203             result add: conflict.
   203             ].
       
   204             commonOffset := (hunks at: lastOverlapHunkIndex) oldChunk lastIndex + 1.
   204             commonOffset := (hunks at: lastOverlapHunkIndex) oldChunk lastIndex + 1.
   205         ] ifFalse: [ 
   205         ] ifFalse: [ 
   206             | conflict |
   206 
   207             conflict := self computeConflictFrom: firstHunkIndex
   207             conflict := self computeConflictFrom: firstHunkIndex
   208                                             to: lastOverlapHunkIndex
   208                                             to: lastOverlapHunkIndex
   209                                             hunks: hunks.
   209                                             hunks: hunks.
   210             result add: conflict.
   210             result add: conflict.
   211             commonOffset := conflict original lastIndex + 1.
   211             commonOffset := conflict original lastIndex + 1.
   214         firstHunkIndex := lastOverlapHunkIndex + 1
   214         firstHunkIndex := lastOverlapHunkIndex + 1
   215     ].
   215     ].
   216     self addCommonChunkTo: result between: commonOffset and: file0 size + 1.
   216     self addCommonChunkTo: result between: commonOffset and: file0 size + 1.
   217     ^ result asArray
   217     ^ result asArray
   218 
   218 
   219     "Modified: / 16-03-2012 / 19:24:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   220     "Created: / 20-03-2012 / 18:27:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   219     "Created: / 20-03-2012 / 18:27:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   221 !
   220 !
   222 
   221 
   223 merge
   222 merge
   224     "Returns an Array of (#ok -> {...}) or (#conflict -> Diff3Conflict 
   223     "Returns an Array of (#ok -> {...}) or (#conflict -> Diff3Conflict 
   296         ^ targetOffset
   295         ^ targetOffset
   297 
   296 
   298     "Modified: / 16-03-2012 / 19:20:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   297     "Modified: / 16-03-2012 / 19:20:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   299 !
   298 !
   300 
   299 
       
   300 computeConflictChunk: side fromCleanMerge: hunk old: old new: new into: conflict
       
   301 
       
   302     side == hunk side ifTrue:[
       
   303         conflict at: side put: hunk newChunk.
       
   304         ^self
       
   305     ].
       
   306     "Hmm....we have to compare"
       
   307 
       
   308 
       
   309     (hunk newChunk extractSafeFrom: (self fileAt: side)) = new ifTrue:[
       
   310         conflict at: side put: hunk newChunk.
       
   311     ] ifFalse:[
       
   312         conflict at: side put: hunk oldChunk.
       
   313     ]
       
   314 
       
   315     "Created: / 06-04-2012 / 12:31:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   316 !
       
   317 
   301 computeConflictFrom: i1 to: i2 hunks: hunks
   318 computeConflictFrom: i1 to: i2 hunks: hunks
   302         | hunk conflict l o r lo ro chunk chunkOrig |
   319         | hunk conflict l o r lo ro chunk chunkOrig |
   303         conflict := Diff3::Conflict new.
   320         conflict := Diff3::Conflict new.
   304         conflict left: (l := Diff2::Chunk negativeSize: file1 size).
   321         conflict left: (l := Diff2::Chunk negativeSize: file1 size).
   305         conflict original: (o := Diff2::Chunk negativeSize: file0 size).
   322         conflict original: (o := Diff2::Chunk negativeSize: file0 size).
   320         r correctForSkewFrom: ro to: o.
   337         r correctForSkewFrom: ro to: o.
   321 
   338 
   322         ^ conflict
   339         ^ conflict
   323 
   340 
   324     "Modified: / 16-03-2012 / 19:20:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   341     "Modified: / 16-03-2012 / 19:20:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   342 !
       
   343 
       
   344 computeConflictFromCleanMerge: hunk
       
   345     | conflict old new |
       
   346 
       
   347     conflict := Conflict new.
       
   348 
       
   349     "/old := hunk oldChunk extractFrom: (self fileAt: hunk side).
       
   350     new := hunk newChunk extractFrom: (self fileAt: hunk side).
       
   351 
       
   352     self computeConflictChunk: #left     fromCleanMerge: hunk old: old new: new into: conflict.
       
   353     self computeConflictChunk: #original fromCleanMerge: hunk old: old new: new into: conflict.
       
   354     self computeConflictChunk: #right    fromCleanMerge: hunk old: old new: new into: conflict.
       
   355 
       
   356     ^conflict.
       
   357 
       
   358     "Created: / 06-04-2012 / 12:13:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   325 !
   359 !
   326 
   360 
   327 computeHunks
   361 computeHunks
   328         | diff2 diff1 hunks |
   362         | diff2 diff1 hunks |
   329         diff1 := self diffClass new file1: file0; file2: file1; diffIndices.
   363         diff1 := self diffClass new file1: file0; file2: file1; diffIndices.
   625 "
   659 "
   626 ! !
   660 ! !
   627 
   661 
   628 !Diff3::Conflict methodsFor:'accessing'!
   662 !Diff3::Conflict methodsFor:'accessing'!
   629 
   663 
       
   664 at: side
       
   665 
       
   666     "Given a side (#left, #original or #right), returns the
       
   667     corresponding chunk"
       
   668 
       
   669     side == #left       ifTrue:[ ^ left ].
       
   670     side == #original   ifTrue:[ ^ original ].
       
   671     side == #right      ifTrue:[ ^ right ].
       
   672 
       
   673     self error:'Invalid parameter, must be one of #left, #original or #right'.
       
   674 
       
   675     "Created: / 06-04-2012 / 12:26:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   676 !
       
   677 
       
   678 at: side put: chunk
       
   679 
       
   680     "Given a side (#left, #original or #right), sets the
       
   681     corresponding chunk"
       
   682 
       
   683     side == #left       ifTrue:[ left := chunk. ^ self].
       
   684     side == #original   ifTrue:[ original := chunk. ^ self ].
       
   685     side == #right      ifTrue:[ right := chunk. ^ self ].
       
   686 
       
   687     self error:'Invalid parameter, must be one of #left, #original or #right'.
       
   688 
       
   689     "Created: / 06-04-2012 / 12:26:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   690 !
       
   691 
       
   692 chunkAt: side
       
   693 
       
   694     "Created: / 06-04-2012 / 12:25:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   695 !
       
   696 
   630 left
   697 left
   631 	^ left
   698 	^ left
   632 !
   699 !
   633 
   700 
   634 left: anObject
   701 left: anObject
   758 ! !
   825 ! !
   759 
   826 
   760 !Diff3 class methodsFor:'documentation'!
   827 !Diff3 class methodsFor:'documentation'!
   761 
   828 
   762 version_SVN
   829 version_SVN
   763     ^ '$Id: Diff3.st 7965 2012-04-04 00:09:32Z vranyj1 $'
   830     ^ '$Id: Diff3.st 7973 2012-04-06 15:56:16Z vranyj1 $'
   764 ! !
   831 ! !