Tools__TextMergeInfo.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Wed, 21 Mar 2012 14:05:42 +0000
branchjv
changeset 12204 ba9ffe0fd036
parent 12203 bcfd4488d8a2
child 12218 8b88c30fb1e7
permissions -rw-r--r--
Fixes in merge tool

"
 COPYRIGHT (c) 2006 by eXept Software AG
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
"{ Package: 'stx:libtool' }"

"{ NameSpace: Tools }"

Object subclass:#TextMergeInfo
	instanceVariableNames:'list listInfos'
	classVariableNames:''
	poolDictionaries:''
	category:'Interface-Diff'
!

Object subclass:#LineInfo
	instanceVariableNames:'line resolution conflict offset'
	classVariableNames:''
	poolDictionaries:''
	privateIn:TextMergeInfo
!

!TextMergeInfo class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 2006 by eXept Software AG
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
! !

!TextMergeInfo methodsFor:'accessing'!

list
    ^ list
!

listInfos
    ^ listInfos
!

text
    ^(list reject:[:l|l isNil]) asString

    "Created: / 19-03-2012 / 14:58:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!TextMergeInfo methodsFor:'initialization'!

text1: text1 text2: text2 text3: text3

    | t1c t2c  t3c merges lnr |

    list := StringCollection new.
    listInfos := OrderedCollection new.

    t1c := (text1 ? #()) asStringCollection.
    t2c := (text2 ? #()) asStringCollection.
    t3c := (text3 ? #()) asStringCollection.


    merges := Diff3 new
                    file0: t1c; "/Base version
                    file1: t2c; "/A
                    file2: t3c; "/B
                    merge.
    lnr := 1.
    merges do:[:merge|
        merge key == #ok ifTrue:[
            merge value do:[:line|
                list add: line.
                listInfos add: (LineInfo line: lnr resolution: #Merged ).
                lnr := lnr + 1.
            ].
        ].
        merge key == #conflict ifTrue:[
            1 to: merge value length do:[:i|
                list add:nil. "/no resolution now"
                listInfos add: (LineInfo line: lnr resolution: #Conflict conflict: merge value offset: i).
                lnr := lnr + 1.
            ].
        ].
    ].

    self changed: #value

    "Created: / 19-03-2012 / 12:10:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!TextMergeInfo methodsFor:'merging'!

mergeUsingA: textA

    list := (textA ? #()) asStringCollection.
    listInfos := 
        (1 to: list size) collect:[:lineNr|
            (LineInfo line: lineNr resolution: #MergedUsingA )
        ].
    self changed:#resulution

    "Created: / 21-03-2012 / 12:03:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

mergeUsingB: textB

    list := (textB ? #())  asStringCollection.
    listInfos := 
        (1 to: list size) collect:[:lineNr|
            (LineInfo line: lineNr resolution: #MergedUsingB )
        ].
    self changed:#resulution

    "Created: / 21-03-2012 / 12:04:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

mergeUsingBase: textBase

    list := (textBase ? #()) asStringCollection.
    listInfos := 
        (1 to: list size) collect:[:lineNr|
            (LineInfo line: lineNr resolution: #MergedUsingBase )
        ].
    self changed:#resulution

    "Created: / 21-03-2012 / 12:07:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!TextMergeInfo methodsFor:'testing'!

isMerged

    ^listInfos allSatisfy:[:info|info isMerged].

    "Created: / 19-03-2012 / 15:09:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!TextMergeInfo::LineInfo class methodsFor:'accessing'!

line:lineArg resolution:resolutionArg
    ^self new 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 

    ^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'!

color

    self isMerged ifTrue:[ 
        self isMergedUsingA ifTrue:[ ^Tools::TextDiff3Tool colorA].
        self isMergedUsingB ifTrue:[ ^Tools::TextDiff3Tool colorB].
        self isMergedUsingBase ifTrue:[ ^Tools::TextDiff3Tool colorBase].
        ^ Tools::TextDiff3Tool colorMerged 
    ].
    self isConflict ifTrue:[ ^ Tools::TextDiff3Tool colorConflict ].
    ^nil

    "Created: / 19-03-2012 / 15:05:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

conflict
    ^ conflict
!

line
    ^ line
!

line:lineArg resolution:resolutionArg
    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 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
    ^ resolution
!

resolution:something
    resolution := something.
! !

!TextMergeInfo::LineInfo methodsFor:'printing & storing'!

printOn:aStream
    "append a printed representation if the receiver to the argument, aStream"

    self class nameWithoutPrefix printOn:aStream.
    aStream space.
    aStream nextPutAll:'line: '.
    line printOn:aStream.
    aStream space.
    aStream nextPutAll:'resolution: '.
    resolution printOn:aStream.

    "Modified: / 19-03-2012 / 12:30:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Created: / 19-03-2012 / 15:05:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!TextMergeInfo::LineInfo methodsFor:'testing'!

isConflict

    ^resolution == #Conflict

    "Created: / 19-03-2012 / 15:06:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

isMerged

    ^(resolution == #Merged) 
        or:[self isMergedUsingA
            or:[self isMergedUsingB
                or:[self isMergedUsingBase]]]

    "Created: / 19-03-2012 / 15:06:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

isMergedUsingA

    ^resolution == #MergedUsingA

    "Created: / 20-03-2012 / 14:21:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

isMergedUsingB

    ^resolution == #MergedUsingB

    "Created: / 20-03-2012 / 14:21:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

isMergedUsingBase

    ^resolution == #MergedUsingBase

    "Created: / 20-03-2012 / 14:21:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!TextMergeInfo class methodsFor:'documentation'!

version_SVN
    ^ '$Id: Tools__TextMergeInfo.st 7951 2012-03-21 14:05:42Z vranyj1 $'
! !