Tools__Diff2CodeView2.st
author Claus Gittinger <cg@exept.de>
Thu, 15 May 2014 19:21:25 +0200
changeset 14371 491ec9ff2c09
parent 13839 e691e2233fa1
child 15278 1d449ea6c8e0
permissions -rw-r--r--
class: Tools::Diff2CodeView2 changed: #computeDiffDataForText1:text2:

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

DiffCodeView2 subclass:#Diff2CodeView2
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'Interface-CodeView'
!

Object subclass:#Diff2Data
	instanceVariableNames:'text1 text2 inserted deleted changed'
	classVariableNames:''
	poolDictionaries:''
	privateIn:Diff2CodeView2
!

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

!Diff2CodeView2 class methodsFor:'defaults'!

numberOfViews
    "return the number of the synced subViews.
     Usually redefined in subclasses"

    ^ 2

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

!Diff2CodeView2 methodsFor:'accessing'!

text1:t1 text2:t2 
    |data|

    data := self computeDiffDataForText1:t1 text2:t2.

    (textViews at:1) 
        contents:(data text1);
        deletedLines:(data deleted);
        changedLines:(data changed);
        insertedLines:#();    
        originDiffText:t1;
        emptyLines:(data inserted).

    (textViews at:2) 
        contents:(data text2);
        deletedLines:#();
        changedLines:(data changed);
        insertedLines:(data inserted);
        originDiffText:t2;
        emptyLines:(data deleted).

    "Created: / 06-03-2010 / 10:45:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 22-06-2010 / 21:36:35 / Jakub <zelenja7@fel.cvut.cz>"
    "Modified: / 15-07-2010 / 23:08:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!Diff2CodeView2 methodsFor:'private'!

computeDiffDataForText1:t1 text2:t2 
    "created diffText object from two string"

    "/ cg: same code as in DiffCodeView2!!!!!!
    "/ please refactor and make this a utility method on the class side

    |array1 array2 diff change index1 index2 text1 text2 i 
     data deleted inserted helperText addConstant1 addConstant2 changed helper ins del pom
     array1Size array2Size|

    "Convert text into an array of individual lines"
    array1 := self createArray:t1.
    array2 := self createArray:t2.
    "Initialize inserted/deleted/changed "
    inserted := OrderedCollection new.
    deleted := OrderedCollection new.
    changed := OrderedCollection new.

     "indicates which row of origin text is added to ne text"
    index1 := 1.
    index2 := 1.
     "indicate how much rows were deleted or inserted "
    addConstant1 := 0.
    addConstant2 := 0.
    text1 := ''.
    text2 := ''.
    diff := Diff new.
    diff a:array1 b:array2.
    change := diff diff:false.
    data := Diff2Data new.



    [ change notNil ] whileTrue:[
        "check first lines which are same"
        (((change line0) > 0) and:[ ((change line1) > 0) ]) ifTrue:[
            [
                index1 <= (change line0)
            ] whileTrue:[
                helperText := (array1 at:index1) asText.
                text1 := text1 asString , helperText asString.
                index1 := index1 + 1.
            ].
            [
                index2 <= (change line1)
            ] whileTrue:[
                helperText := (array2 at:index2) asText.
                text2 := text2 , helperText.
                index2 := index2 + 1.
            ].
        ].
        ins := change inserted.
        del := change deleted.
        index1 := (change line0) + 1.
        index2 := (change line1) + 1.
         "find replace files "
        ((del > 0) and:[ ins > 0 ]) ifTrue:[
            helper := del - ins.
            (helper <= 0) ifTrue:[
                pom := change deleted.
            ].
            (helper > 0) ifTrue:[
                pom := change inserted.
            ].
             "its same count row"
            i := 1.
            [ i <= pom ] whileTrue:[
                changed add:index1 + addConstant1.
                text1 := text1 , (array1 at:index1) asString.
                text2 := text2 , (array2 at:index2) asString.
                index1 := index1 + 1.
                index2 := index2 + 1.
                del := del - 1.
                ins := ins - 1.
                i := i + 1.
            ].
        ].
         "find deleted files"
        (del > 0) ifTrue:[
            i := 1.
            [ i <= del ] whileTrue:[
                deleted add:index1 + addConstant1.
                text2 := text2 , Character cr.
                addConstant2 := addConstant2 + 1.
                text1 := text1 , (array1 at:index1) asString.
                index1 := index1 + 1.
                i := i + 1.
            ].
        ].
         "find inserted lines"
        (ins > 0) ifTrue:[
            i := 1.
            [ i <= ins ] whileTrue:[
                inserted add:index2 + addConstant2.
                text1 := text1 , Character cr.
                addConstant1 := addConstant1 + 1.
                text2 := text2 , (array2 at:index2) asString.
                index2 := index2 + 1.
                i := i + 1.
            ].
        ].
        change := change nextLink.
    ].
     "kontrola zda nam nechybi posledni znaky"
    array1Size := array1 size.
    (index1 <= array1Size) ifTrue:[
        [ index1 <= array1Size ] whileTrue:[
            helperText := (array1 at:index1) asText.
            text1 := text1 , helperText.
            index1 := index1 + 1.
        ].
    ].
    array2Size := array2 size.
    (index2 <= array2Size) ifTrue:[
        [ index2 <= (array2 size) ] whileTrue:[
            helperText := (array2 at:index2) asText.
            text2 := text2 , helperText.
            index2 := index2 + 1.
        ].
    ].
    data text1:text1.
    data text2:text2.
    data changed:changed.
    data inserted:inserted.
    data deleted:deleted.
    ^ data.

    "Modified: / 22-06-2010 / 21:02:50 / Jakub <zelenja7@fel.cvut.cz>"
    "Modified: / 16-03-2012 / 12:53:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (format): / 16-03-2012 / 16:10:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

createArray:text1 

    | array src line c |
    array := StringCollection new.
    src := text1 readStream.
    line := (String new: 80) writeStream.
    [ src atEnd ] whileFalse:[
        c := src next.
        line nextPut: c.
        c == Character cr ifTrue:[
            array add: line contents.
            line reset.
        ]        
    ].
    line position ~~ 0 ifTrue:[
        array add: line contents
    ].
    ^array

    "Created: / 22-03-2010 / 14:48:27 / Jakub <zelenja7@fel.cvut.cz>"
    "Modified (comment): / 19-07-2011 / 11:14:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!Diff2CodeView2::Diff2Data methodsFor:'accessing'!

changed

    ^changed copy

    "Modified: / 02-05-2010 / 19:31:18 / Jakub <zelenja7@fel.cvut.cz>"
    "Modified: / 16-07-2010 / 09:35:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

changed:something
    changed := something.
!

deleted
    ^ deleted
!

deleted:something
    deleted := something.
!

inserted
    ^ inserted
!

inserted:something
    inserted := something.
!

text1
    ^ text1
!

text1:something
    text1 := something.
!

text2
    ^ text2
!

text2:something
    text2 := something.
! !

!Diff2CodeView2 class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libtool/Tools__Diff2CodeView2.st,v 1.2 2014-05-15 17:21:25 cg Exp $'
!

version_CVS
    ^ '$Header: /cvs/stx/stx/libtool/Tools__Diff2CodeView2.st,v 1.2 2014-05-15 17:21:25 cg Exp $'
! !