DiffTextView.st
author Claus Gittinger <cg@exept.de>
Fri, 30 Jan 1998 12:24:57 +0100
changeset 1440 6a68adba9c33
parent 1276 66761d461a39
child 2141 1758f387ebe7
permissions -rw-r--r--
allow configuration of diff command; preset correctly for UNIX & MSDOS

"
 COPYRIGHT (c) 1994 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.
"

TwoColumnTextView subclass:#DiffTextView
	instanceVariableNames:'useColors showSeparators addedColor addedBgColor removedColor
		removedBgColor changedColor changedBgColor changedSpacesOnlyColor
		changedSpacesOnlyBgColor diffLineNumbers'
	classVariableNames:'DiffCommandTemplate'
	poolDictionaries:''
	category:'Views-Text'
!

!DiffTextView class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1994 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 diff output (see unix manual pages)
    in a user-friendly form.
    The view is created and opened with:

        d := DiffTextView openOn:text1 and:text2

    or:
        d := DiffTextView openOn:text1 label:l1
                             and:text2 label:l2

    and it will show the differences side-by-side.

    For a real world application, 
    see the ChangesBrowsers `compare' function.

    [see also:]
        TextView EditTextView Diff3TextView

    [author:]
        Claus Gittinger
"
!

examples
"
                                                        [exBegin]
    |text1 text2|

    text1 := 'hello world
here is some difference
more text
this line has been removed
more text
more text
'.

    text2 := 'hello world
where is the difference ?
more text
more text
more text
this line has been added
'.

    DiffTextView openOn:text1 label:'text1'
                    and:text2 label:'text2'
                                                        [exEnd]
"
! !

!DiffTextView class methodsFor:'defaults'!

diffCommand
    "return the diff-command (with argument placeHolders)"

    OperatingSystem isMSDOSlike ifTrue:[
        ^ DiffCommandTemplate ? 'diff %1 %2'
    ].

    ^ DiffCommandTemplate ? 'diff -b %1 %2'

    "Modified: / 30.1.1998 / 12:12:49 / cg"
!

diffCommandTemplate:aCommandTemplateString
    "set the diff-command template"

    OperatingSystem isMSDOSlike ifTrue:[
        ^ DiffCommandTemplate ? 'diff %1 %2'
    ].

    ^ DiffCommandTemplate ? 'diff -b %1 %2'

    "Modified: / 30.1.1998 / 12:10:34 / cg"
    "Created: / 30.1.1998 / 12:12:37 / cg"
! !

!DiffTextView methodsFor:'accessing'!

text1:t1 text2:t2
    "set the two texts which are to be diffed;
     execute DiffCommand and update the two textViews."

    |tmpFile1 tmpFile2 name1 tmpName2 stream line 
     text1 text2 diffList pidString diffCmd|

    text1 := t1 asStringCollection.
    text2 := t2 asStringCollection.

    "
     save them texts in two temporary files ...
    "
    tmpFile1 := Filename newTemporary.
    stream := tmpFile1 writeStream.
    text1 do:[:line |
        stream nextPutAll:line; cr
    ].
    stream close.

    tmpFile2 := Filename newTemporary.
    stream := tmpFile2 writeStream.
    text2 do:[:line |
        stream nextPutAll:line; cr
    ].
    stream close.

    "
     start diff on it ...
    "
    diffCmd := self class diffCommand 
                    bindWith:tmpFile1 asString
                    with:tmpFile2 asString.

    stream := PipeStream readingFrom:diffCmd.
    stream isNil ifTrue:[
        self error:'cannot execute diff'.
        text1 := text2 := nil.
    ] ifFalse:[
        diffList := OrderedCollection new.
        [stream atEnd] whileFalse:[
            line := stream nextLine.
            line notNil ifTrue:[diffList add:line]
        ].
        stream close.
    ].

    tmpFile1 delete.
    tmpFile2 delete.

    self updateListsFrom:text1 and:text2 diffs:diffList

    "
     |v|

     v := HVScrollableView for:DiffTextView.
     v scrolledView text1:('../libview/Color.st' asFilename readStream contents)
                    text2:('../libview/Color.st.old' asFilename readStream contents).
     v open
    "

    "
     |v t1 t2|

     t1 := '
one
two
three
four
'.
     t2 := '
one
two-a
two-b
three
three-b
four
'.

     v := DiffTextView new.
     v text1:t1 text2:t2.
     v open
    "

    "Modified: / 30.1.1998 / 12:12:13 / cg"
! !

!DiffTextView methodsFor:'initialization'!

initStyle
    super initStyle.

    showSeparators := false.

    (useColors := device hasColors) ifTrue:[
        addedColor := Color black.
        addedBgColor := Color green.

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

        changedColor := Color white.
        changedBgColor := Color blue.

        changedSpacesOnlyColor := Color white.
        changedSpacesOnlyBgColor := Color blue lightened.
    ] ifFalse:[
        showSeparators := true.

        (useColors := device hasGreyscales) ifTrue:[
            addedBgColor := removedBgColor := changedBgColor := Color grey:80.
            addedColor := removedColor := changedColor := Color black.
        ] ifFalse:[
            addedBgColor := removedBgColor := changedBgColor := Color black.
            addedColor := removedColor := changedColor := Color white.
        ].

        changedSpacesOnlyColor := Color white.
        changedSpacesOnlyBgColor := Color black.
    ].

    "Created: 16.11.1995 / 16:59:48 / cg"
    "Modified: 14.6.1996 / 16:14:39 / cg"
! !

!DiffTextView methodsFor:'private'!

updateListsFrom:text1 and:text2 diffs:diffList
    "given the two texts in text1 and text2, and the diff-output in diffList,
     update my views contents"

    |idx1 idx2 dIdx dEnd state s nr1 nr2 nr3 op entry c l1 l2 any delta
     textView1 textView2 s1 s2|

    diffLineNumbers := OrderedCollection new.

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

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

    idx1 := 1.
    idx2 := 1.

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

        state == #initial ifTrue:[
            "entry is of the form <nr> <op> <offs> [<offs2>]"

            "
             fill up to size difference from previous change
            "
            delta := l1 size - l2 size.
            delta > 0 ifTrue:[
                delta timesRepeat:[l2 add:nil]
            ] ifFalse:[
                delta < 0 ifTrue:[
                    delta negated timesRepeat:[l1 add:nil]
                ]
            ].

            "
             except for the first chunk, add a separating line
            "
            l1 size ~~ 0 ifTrue:[
                showSeparators ifTrue:[
                    l1 add:'--------'.
                    l2 add:'--------'.
                ]
            ].
            "
             in cleanup ?
            "
            entry isNil ifTrue:[
                nr1 := text1 size + 1.
                nr2 := text2 size + 1.
                state := #finish.
            ] ifFalse:[
                diffLineNumbers add:l1 size.

                s := ReadStream on:entry.
                nr1 := Integer readFrom:s.
                s peek == $, ifTrue:[
                    s next.
                    Integer readFrom:s
                ].
                op := s next.
                nr2 := Integer readFrom:s.
                s peek == $, ifTrue:[
                    s next.
                    nr3 := Integer readFrom:s
                ] ifFalse:[
                    nr3 := nil
                ].

                op == $c ifTrue:[
                    state := #changed.
                ] ifFalse:[
                    op == $a ifTrue:[
                        state := #added.
                    ] ifFalse:[
                        op == $d ifTrue:[
                            state := #deleted
                        ] ifFalse:[
                            self halt:'unexpected diff entry'.
                        ]
                    ]
                ].

            ].

"/ nr1 print. ' ' print. op print. ' ' print. nr2 print. ' , ' print. nr3 printNL.

            "
             copy over unchanged lines
            "
            any := false.
            [idx1 < nr1] whileTrue:[
"/ '< add:' print. idx1 printNL.
                l1 add:(text1 at:idx1).
                idx1 := idx1 + 1.
                any := true.
            ].
            [idx2 < nr2] whileTrue:[
"/ '> add:' print. idx2 printNL.
                l2 add:(text2 at:idx2).
                idx2 := idx2 + 1.
                any := true.
            ].

            state == #added ifTrue:[
                l1 add:(text1 at:idx1).
                idx1 := idx1 + 1.
            ].
            state == #deleted ifTrue:[
                l2 add:(text2 at:idx2).
                idx2 := idx2 + 1.
            ].


            "
             add a separating line, except at end
            "
            any ifTrue:[
                state ~~ #finish ifTrue:[
                    showSeparators ifTrue:[
                        l1 add:'--------'.
                        l2 add:'--------'.
                    ]
                ]
            ].

        ] ifFalse:[
            state == #changed ifTrue:[
                (entry at:1) == $< ifTrue:[
                    useColors ifTrue:[
                        (l2 size >= idx1
                        and:[(s2 := l2 at:idx1) notNil
                             and:[s2 asString withoutSeparators = (text1 at:idx1) withoutSeparators]]) ifTrue:[
                            l1 add:(Text string:(text1 at:idx1) 
                                         foregroundColor:changedSpacesOnlyColor
                                         backgroundColor:changedSpacesOnlyBgColor).
                            l2 at:idx1 put:(Text string:(l2 at:idx1) asString 
                                                 foregroundColor:changedSpacesOnlyColor 
                                                 backgroundColor:changedSpacesOnlyBgColor).
                        ] ifFalse:[
                            l1 add:(Text string:(text1 at:idx1) 
                                         foregroundColor:changedColor 
                                         backgroundColor:changedBgColor).
                        ]
                    ] ifFalse:[
                        l1 add:(text1 at:idx1).
                    ].
                    idx1 := idx1 + 1
                ] ifFalse:[
                    (entry at:1) == $> ifTrue:[
                        useColors ifTrue:[
                            (l1 size >= idx2
                            and:[(s1 := l1 at:idx2) notNil
                                and:[s1 asString withoutSeparators = (text2 at:idx2) withoutSeparators]]) ifTrue:[
                                l2 add:(Text string:(text2 at:idx2) foregroundColor:changedSpacesOnlyColor backgroundColor:changedSpacesOnlyBgColor).
                                l1 at:idx2 put:(Text string:(l1 at:idx2) asString foregroundColor:changedSpacesOnlyColor backgroundColor:changedSpacesOnlyBgColor).
                            ] ifFalse:[
                                l2 add:(Text string:(text2 at:idx2) foregroundColor:changedColor backgroundColor:changedBgColor)
                            ]
                        ] ifFalse:[
                            l2 add:(text2 at:idx2).
                        ].
                        idx2 := idx2 + 1
                    ] ifFalse:[
                        (entry at:1) == $- ifTrue:[
                        ] ifFalse:[
                            state := #initial.
                            dIdx := dIdx - 1
                        ]
                    ]
                ]
            ] ifFalse:[
                state == #added ifTrue:[
                    (entry at:1) == $> ifTrue:[
                        useColors ifTrue:[
                            l2 add:(Text string:(text2 at:idx2) foregroundColor:addedColor backgroundColor:addedBgColor )
                        ] ifFalse:[
                            l2 add:(text2 at:idx2).
                        ].
                        idx2 := idx2 + 1.
                        l1 add:nil
                    ] ifFalse:[
                        state := #initial.
                        dIdx := dIdx - 1
                    ]
                ] ifFalse:[
                    state == #deleted ifTrue:[
                        (entry at:1) == $< ifTrue:[
                            useColors ifTrue:[
                                l1 add:(Text string:(text1 at:idx1) foregroundColor:removedColor backgroundColor:removedBgColor ).
                            ] ifFalse:[
                                l1 add:(text1 at:idx1).
                            ].
                            idx1 := idx1 + 1.
                            l2 add:nil
                        ] ifFalse:[
                            state := #initial.
                            dIdx := dIdx - 1
                        ]
                    ] 
                    "must be in finish otherwise"
                ]
            ]
        ].
        dIdx := dIdx + 1
    ].
    [l1 size < l2 size] whileTrue:[
        l1 add:''.
    ].
    [l2 size < l1 size] whileTrue:[
        l2 add:''.
    ].
    textView1 list:l1.
    textView2 list:l2

    "Modified: 16.5.1996 / 12:38:49 / cg"
! !

!DiffTextView class methodsFor:'documentation'!

version
^ '$Header: /cvs/stx/stx/libtool/DiffTextView.st,v 1.22 1998-01-30 11:24:57 cg Exp $'! !