DiffTextView.st
author claus
Thu, 17 Nov 1994 15:47:59 +0100
changeset 52 7b48409ae088
parent 45 950b84ba89e6
child 69 0d6acfdae045
permissions -rw-r--r--
*** empty log message ***

"
 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:''
	 classVariableNames:''
	 poolDictionaries:''
	 category:'Views-Text'
!

DiffTextView comment:'
COPYRIGHT (c) 1994 by Claus Gittinger
	      All Rights Reserved

$Header: /cvs/stx/stx/libtool/DiffTextView.st,v 1.4 1994-11-17 14:46:45 claus Exp $
'!

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

version
"
$Header: /cvs/stx/stx/libtool/DiffTextView.st,v 1.4 1994-11-17 14:46:45 claus Exp $
"
!

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

       d := DiffTextView openOn:text1 and:text2.

    and it will show the differences side-by-side
    For a real world application, see the ChangesBrowsers
    compare function.
"
! !

!DiffTextView class methodsFor:'defaults'!

diffCommand
    ^ 'diff -b'
! !

!DiffTextView methodsFor:'private'!

updateListsFrom:text1 and:text2 diffs:diffList
    |idx1 idx2 dIdx dEnd state s nr1 nr2 nr3 op entry c l1 l2 any delta|

    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:[
		l1 add:'--------'.
		l2 add:'--------'.
	    ].

	    "
	     in cleanup ?
	    "
	    entry isNil ifTrue:[
		nr1 := text1 size + 1.
		nr2 := text2 size + 1.
		state := #finish.
	    ] ifFalse:[
		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.
			l1 add:(text1 at:idx1).
			idx1 := idx1 + 1.
		    ] ifFalse:[
			op == $d ifTrue:[
			    state := #deleted
			]
		    ]
		].

	    ].

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

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

	] ifFalse:[
	    state == #changed ifTrue:[
		(entry at:1) == $< ifTrue:[
		    l1 add:(text1 at:idx1).
		    idx1 := idx1 + 1
		] ifFalse:[
		    (entry at:1) == $> ifTrue:[
			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:[
			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:[
			    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
! !

!DiffTextView methodsFor:'accessing'!

text1:t1 text2:t2
    |tmpName1 tmpName2 stream line text1 text2 diffList|

    text1 := t1 asText.
    text2 := t2 asText.

    "
     save them texts in two temporary files ...
    "
    tmpName1 := '/tmp/sta_' , OperatingSystem getProcessId printString , '.tmp'.
    tmpName2 := '/tmp/stb_' , OperatingSystem getProcessId printString , '.tmp'.

    stream := tmpName1 asFilename writeStream.
    text1 do:[:line |
	stream nextPutAll:line; cr
    ].
    stream close.

    stream := tmpName2 asFilename writeStream.
    text2 do:[:line |
	stream nextPutAll:line; cr
    ].
    stream close.

    "
     start diff on it ...
    "
    stream := PipeStream 
		readingFrom:self class diffCommand , ' ' , 
			    tmpName1 , ' ' , tmpName2.
    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.
    ].

    tmpName1 asFilename delete.
    tmpName2 asFilename 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
    "
! !