Tools__TextMergeInfo.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Mon, 19 Mar 2012 15:32:45 +0000
branchjv
changeset 12198 414e7b69ecda
child 12201 283826cb8bcc
permissions -rw-r--r--
Text/ChangeSet diff improved

"
 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'
	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 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.

    text1 isNil ifTrue:[ ^self ].
    text2 isNil ifTrue:[ ^self ].
    text2 isNil ifTrue:[ ^self ].


    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:[
            merge value length timesRepeat:[
                list add:nil. "/no resolution now"
                listInfos add: (LineInfo line: lnr resolution: #Conflict conflict: merge value).
                lnr := lnr + 1.
            ].
        ].
    ].

    self changed: #value

    "Created: / 19-03-2012 / 12:10:55 / 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

    "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>"
! !

!TextMergeInfo::LineInfo methodsFor:'accessing'!

color

    self isMerged ifTrue:[ ^ Tools::TextDiff3Tool colorMerged ].
    self isConflict ifTrue:[ ^ Tools::TextDiff3Tool colorConflict ].

    "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

    "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.
!

resolution
    ^ resolution
! !

!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

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

!TextMergeInfo class methodsFor:'documentation'!

version_SVN
    ^ '$Id: Tools__TextMergeInfo.st 7944 2012-03-19 15:32:45Z vranyj1 $'
! !