initial checkin
authorClaus Gittinger <cg@exept.de>
Sat, 10 Oct 2009 12:08:51 +0200
changeset 8933 94e708e9f812
parent 8932 bd3f49d77ecb
child 8934 7cc2affd9bb9
initial checkin
DiffListUtility.st
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/DiffListUtility.st	Sat Oct 10 12:08:51 2009 +0200
@@ -0,0 +1,196 @@
+"{ Package: 'stx:libtool' }"
+
+Object subclass:#DiffListUtility
+	instanceVariableNames:''
+	classVariableNames:'DiffCommandTemplate'
+	poolDictionaries:''
+	category:'Views-Text'
+!
+
+!DiffListUtility class methodsFor:'documentation'!
+
+documentation
+"
+    a utility to encapsulate access to the diff command
+    (may be a facede to a smalltalk-diff algorithm, eventually)
+
+    [author:]
+        cg (cg@CG-PC)
+
+    [instance variables:]
+
+    [class variables:]
+
+    [see also:]
+
+"
+! !
+
+!DiffListUtility class methodsFor:'defaults'!
+
+diffCommand
+    "return the diff-command (with argument placeHolders)"
+
+    DiffCommandTemplate notNil ifTrue:[ ^ DiffCommandTemplate ].
+
+    OperatingSystem isMSDOSlike ifTrue:[
+        (OperatingSystem canExecuteCommand:'diff') ifFalse:[
+            'DiffTextView [warning]: no diff command found (please download and unzip "UnxUtils.zip" from "unxutils.sourceforge.net")' infoPrintCR.
+            ^ nil
+        ].
+        ^ 'diff %1 %2'
+    ].
+    ^ 'diff -b %1 %2'
+
+    "Modified: / 30.1.1998 / 12:12:49 / cg"
+!
+
+diffCommandTemplate:aCommandTemplateString
+    "set the diff-command template"
+
+    DiffCommandTemplate := aCommandTemplateString
+! !
+
+!DiffListUtility class methodsFor:'private'!
+
+saveForDiff:text as:filename
+    |stream|
+
+    [
+        stream := filename writeStream.
+        text do:[:line |
+            |lOut i|
+
+            line notEmptyOrNil ifTrue:[
+                lOut := line.
+                (line includes:Character return) ifTrue: [
+                    (line endsWith:Character return) ifTrue:[
+                        lOut := line copyWithoutLast:1.
+                    ] ifFalse:[
+                        i := line indexOf:Character return.
+                        (line at:i+1) == Character nl ifTrue:[
+                            "/ crnl endings
+                            lOut := line copyReplaceString:(String crlf) withString:(String lf).
+                        ] ifFalse:[
+                            "/ cr endings
+                            lOut := line copyReplaceAll:Character return with:Character nl.
+                        ].
+                    ]
+                ].
+                lOut bitsPerCharacter > 8 ifTrue:[
+                    (lOut first = (Character value:16rFEFF)) ifTrue:[
+                        lOut := (lOut copyFrom:2) asSingleByteStringIfPossible.
+                    ].
+                    lOut bitsPerCharacter > 8 ifTrue:[ 
+                        lOut := lOut collect:[:ch | ch bitsPerCharacter > 8 
+                                                        ifTrue:[ Character value:16rFF ]
+                                                        ifFalse:[ ch ]].
+                        lOut := lOut asSingleByteStringIfPossible.
+                    ].
+                ].
+                stream nextPutAll:lOut.
+            ].
+            stream cr
+        ].
+    ] ensure:[
+        stream close.
+    ].
+
+    "Modified: / 22-10-2008 / 17:52:52 / cg"
+! !
+
+!DiffListUtility class methodsFor:'utilities'!
+
+diffListFor:text1 and:text2
+    "execute DiffCommand to get a list of diffs."
+
+    "
+     The returned list is in raw-diff output format, such as:
+        1 : '1c1'
+        2 : '< hello world'
+        3 : '---'
+        4 : '> Hello World'
+        5 : '2a3'
+        6 : '> line2'
+        7 : '4d4'
+        8 : '< line4'
+    "
+
+    |tmpFile1 tmpFile2 stream line 
+     diffList diffTemplate diffCmd|
+
+    diffTemplate := self diffCommand.
+    diffTemplate isNil ifTrue:[
+        "/ self warn:'no diff command available'.
+        ^ nil
+    ].
+
+    text1 = text2 ifTrue:[
+        "no diff"
+        ^ #()
+    ].
+
+    "
+     save them texts in two temporary files ...
+    "
+    [
+        self saveForDiff:text1 as:(tmpFile1 := Filename newTemporary).
+        self saveForDiff:text2 as:(tmpFile2 := Filename newTemporary).
+
+        "
+         start diff on it ...
+        "
+        diffCmd := diffTemplate
+                    bindWith:tmpFile1 asString
+                    with:tmpFile2 asString.
+
+        stream := PipeStream readingFrom:diffCmd.
+        stream isNil ifTrue:[
+            stream := PipeStream readingFrom:('support' , Filename separator , diffCmd).
+            stream isNil ifTrue:[
+                self error:'cannot execute diff' mayProceed:true.
+                ^ nil.
+            ]
+        ].
+
+        diffList := OrderedCollection new.
+        (stream readWaitWithTimeout:10) ifTrue:[
+            "/ timeout
+            stream close.
+            self error:'cannot execute diff (timeout)' mayProceed:true.
+            ^ nil.
+        ].
+
+        [stream atEnd] whileFalse:[
+            line := stream nextLine.
+            line notNil ifTrue:[diffList add:line]
+        ].
+        stream close.
+    ] ensure:[
+        tmpFile1 notNil ifTrue:[ tmpFile1 delete ].
+        tmpFile2 notNil ifTrue:[ tmpFile2 delete ].
+    ].
+    ^ diffList
+
+    "
+     self 
+        diffListFor:#(
+                        'hello world'
+                        'line1'
+                        'line3'
+                        'line4'
+                    )
+        and:        #(
+                        'Hello World'
+                        'line1'
+                        'line2'
+                        'line3'
+                    )
+    "
+! !
+
+!DiffListUtility class methodsFor:'documentation'!
+
+version_CVS
+    ^ '$Header: /cvs/stx/stx/libtool/DiffListUtility.st,v 1.1 2009-10-10 10:08:51 cg Exp $'
+! !