Diff3TextView.st
author Claus Gittinger <cg@exept.de>
Tue, 12 Dec 1995 14:47:12 +0100
changeset 277 b4b2782bc733
parent 271 16d2d5f9c31c
child 290 5b9361cfa7b8
permissions -rw-r--r--
documentation

"
 COPYRIGHT (c) 1995 by Claus Gittinger
              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.
"

ThreeColumnTextView subclass:#Diff3TextView
	instanceVariableNames:'useColors showSeparators addedColor addedBgColor removedColor
		removedBgColor changedColor changedBgColor'
	classVariableNames:''
	poolDictionaries:''
	category:'Views-Text'
!

!Diff3TextView class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1995 by Claus Gittinger
              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.
"
!

documentation
"
    a view showing merged diff3 (see rcsmerge / merge unix manual pages) output in a 
    user-friendly form.
    The view is created and opened with:

       d := Diff3TextView openOn:text label:l1 label:l2 label:l3.

    and it will show the 3 versions side-by-side
    Its main use is for the SourceCodeManager, to show merged sources after
    a failed checkin.
"
! !

!Diff3TextView class methodsFor:'instance creation'!

openOnMergedText:text label:firstLabel label:secondLabel label:thirdLabel
    "open up a view showing firstText, secondText and thirdText side-by-side,
     and labels for all views."

    |top v l1 l2 l3|

    top := StandardSystemView label:'three texts'.

    l1 := Label label:firstLabel in:top.
    l1 origin:0.0@0.0 corner:0.33@(l1 height).
    l2 := Label label:secondLabel in:top.
    l2 origin:0.33@0.0 corner:0.67@(l1 height).
    l3 := Label label:thirdLabel in:top.
    l3 origin:0.67@0.0 corner:1.0@(l1 height).

    v := HVScrollableView 
               for:self 
               miniScrollerH:true miniScrollerV:false
               in:top.
    v origin:0.0 @ (l1 height + ViewSpacing) corner:1.0 @ 1.0.
    v scrolledView updateListsFromMergedText:text.
    ^ top open

    "
     ThreeColumnTextView
        openOn:('smalltalk.rc' asFilename contentsOfEntireFile)
        label:'smalltalk.rc'
        and:('display.rc' asFilename contentsOfEntireFile)
        label:'display.rc'
        and:('private.rc' asFilename contentsOfEntireFile)
        label:'private.rc'
    "

    "Modified: 12.12.1995 / 13:09:13 / cg"
! !

!Diff3TextView methodsFor:'initialization'!

initStyle
    super initStyle.

    showSeparators := false.

    useColors := ColoredListEntry notNil.
    useColors ifTrue:[
	device hasColors ifTrue:[
	    addedColor := Color black.
	    addedBgColor := Color green.

	    removedColor := Color white.
	    removedBgColor := Color red.

	    changedColor := Color white.
	    changedBgColor := Color blue.
	] ifFalse:[
	    addedBgColor := removedBgColor := changedBgColor := Color black.
	    addedColor := removedColor := changedColor := Color white.
	]
    ].

    "Created: 16.11.1995 / 16:59:48 / cg"
    "Modified: 12.12.1995 / 12:25:55 / cg"
! !

!Diff3TextView methodsFor:'private'!

updateListsFromMergedText:mergedText
    "given the merge()/rcsmerge() merged output (as created by 'cvs update'),
     update my views contents"

    |idx1 idx2 idx3 dIdx dEnd state s nr1 nr2 nr3 entry c l1 l2 l3  
     textView1 textView2 textView3 skip max|

    textView1 := textViews at:1.
    textView2 := textViews at:2.
    textView3 := textViews at:3.

    l1 := OrderedCollection new.
    l2 := OrderedCollection new.
    l3 := OrderedCollection new.

    idx1 := 1.
    idx2 := 1.
    idx3 := 1.

    dIdx := 1.
    dEnd := mergedText size + 1.
    state := #initial.
    [dIdx < dEnd] whileTrue:[
        dIdx == dEnd ifTrue:[
            "dummy cleanup entry"
            entry := nil.
            state := #initial.
        ] ifFalse:[
            entry := mergedText at:dIdx.
            dIdx := dIdx + 1.
        ].

        state == #initial ifTrue:[
            "
             fill up to size difference from previous change
            "
            max := (l1 size max:l2 size) max:l3 size.
            [l1 size < max] whileTrue:[
                l1 add:nil
            ].
            [l2 size < max] whileTrue:[
                l2 add:nil
            ].
            [l3 size < max] whileTrue:[
                l3 add:nil
            ].
        
            "
             except for the first chunk, add a separating line
            "
            l1 size ~~ 0 ifTrue:[
                showSeparators ifTrue:[
                    l1 add:'--------'.
                    l2 add:'--------'.
                    l3 add:'--------'.
                ]
            ].
        ].

        skip := false.

        entry notNil ifTrue:[
            (entry startsWith:'<<<<<<<') ifTrue:[
                state := 1. skip := true.
            ] ifFalse:[
                (entry startsWith:'|||||||') ifTrue:[
                    state := 2. skip := true.
                ] ifFalse:[
                    (entry startsWith:'=======') ifTrue:[
                        state := 3. skip := true.
                    ] ifFalse:[
                        (entry startsWith:'>>>>>>>') ifTrue:[
                            state := #initial.
                            skip := true.
                        ]
                    ]
                ]
            ].

            skip ifFalse:[
                (state == #initial or:[state == 1]) ifTrue:[
                    (useColors and:[state == 1]) ifTrue:[
                        l1 add:(ColoredListEntry string:entry foregroundColor:changedColor backgroundColor:changedBgColor).
                    ] ifFalse:[
                        l1 add:entry
                    ]
                ].
                (state == #initial or:[state == 2]) ifTrue:[
                    (useColors and:[state == 2]) ifTrue:[
                        l2 add:(ColoredListEntry string:entry foregroundColor:changedColor backgroundColor:changedBgColor).
                    ] ifFalse:[
                        l2 add:entry
                    ]
                ].
                (state == #initial or:[state == 3]) ifTrue:[
                    (useColors and:[state == 3]) ifTrue:[
                        l3 add:(ColoredListEntry string:entry foregroundColor:changedColor backgroundColor:changedBgColor).
                    ] ifFalse:[
                        l3 add:entry
                    ]
                ].
            ].
        ].
    ].
        
    textView1 list:l1.
    textView2 list:l2.
    textView3 list:l3.

    "Modified: 12.12.1995 / 13:16:08 / cg"
! !

!Diff3TextView class methodsFor:'documentation'!

version
^ '$Header: /cvs/stx/stx/libtool/Diff3TextView.st,v 1.2 1995-12-12 13:47:12 cg Exp $'
! !