RegressionTests__CompressionStreamTest.st
changeset 1793 f5625dd55555
child 1815 6b8e8ac5e2db
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/RegressionTests__CompressionStreamTest.st	Wed Oct 11 14:20:17 2017 +0200
@@ -0,0 +1,488 @@
+"
+ COPYRIGHT (c) 2002 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:goodies/regression' }"
+
+"{ NameSpace: RegressionTests }"
+
+TestCase subclass:#CompressionStreamTest
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'tests-Regression-Streams'
+!
+
+!CompressionStreamTest class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2002 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.
+"
+!
+
+documentation
+"
+    extracted testCases from CompressionStream
+"
+! !
+
+!CompressionStreamTest class methodsFor:'tests'!
+
+compress
+    "
+     self compress
+    "
+   |fileContents in zip out|
+
+   fileContents := 'symbols.stc' asFilename contentsOfEntireFile.
+
+   in  := fileContents readStream.
+   out := FileStream newFileNamed:'YYY.gz'.
+   out ifNil:[ ^ self ].
+   [ 
+      zip := ZipStream writeOpenOn:out.
+
+     [in atEnd] whileFalse:[ |buf|
+        buf := in nextAvailable:512.
+        buf do:[:n|
+            zip nextPut:n
+        ]
+     ].
+   ] ensure:[
+        zip notNil ifTrue:[ zip close ].
+        out isOpen ifTrue: [ out close ].
+   ].
+!
+
+compress:fn
+    "
+     self compress
+    "
+   |fileContents in zip out|
+
+   fileContents := fn asFilename contentsOfEntireFile.
+
+   in  := fileContents readStream.
+   out := FileStream newFileNamed:'YYY.gz'.
+   out ifNil:[ ^ self ].
+   [ 
+      zip := ZipStream writeOpenOn:out.
+
+     [in atEnd] whileFalse:[ |buf|
+        buf := in nextAvailable:512.
+        buf do:[:n|
+            zip nextPut:n
+        ]
+     ].
+   ] ensure:[
+        zip notNil ifTrue:[ zip close ].
+        out close.
+   ].
+!
+
+testUncompress
+    "
+     self testUncompress #(521755 686495 false)  #(521755 686495 false)
+    "
+    |stream zipStream contents contentsOfOriginal|
+
+    [
+        stream    := 'YYY.gz' asFilename readStream.
+        zipStream := ZipStream readOpenOn:stream.
+        contents  := zipStream contents.
+    ] ensure:[
+        zipStream notNil ifTrue:[zipStream close].
+        stream    notNil ifTrue:[stream close].
+    ]. 
+    stream := 'symbols.stc' asFilename readStream.
+    contentsOfOriginal := stream contentsOfEntireFile.
+    stream close.
+    ^ Array with: contents size
+            with: contentsOfOriginal size
+            with: contents = contentsOfOriginal.
+!
+
+testUncompress: fn
+    "
+     (self testUncompress: 'symbols.stc') inspect
+    "
+    |stream zipStream contents contentsOfOriginal|
+
+    self compress: fn.
+    [
+        stream    := 'YYY.gz' asFilename readStream.
+        zipStream := ZipStream readOpenOn:stream.
+        contents  := zipStream contents.
+    ] ensure:[
+        zipStream notNil ifTrue:[zipStream close].
+        stream    notNil ifTrue:[stream close].
+    ]. 
+    stream := fn asFilename readStream.
+    contentsOfOriginal := stream contentsOfEntireFile.
+    stream close.
+    ^ Array with: contents size
+            with: contentsOfOriginal size
+            with: contents = contentsOfOriginal.
+!
+
+uncompress
+    "
+     self uncompress
+    "
+    |stream zipStream contents|
+
+    [
+        stream    := 'YYY.gz' asFilename readStream.
+        zipStream := ZipStream readOpenOn:stream.
+        contents  := zipStream contents.
+    ] ensure:[
+        zipStream notNil ifTrue:[zipStream close].
+        (stream   notNil and: [stream isOpen]) ifTrue:[stream close].
+    ].        
+    ^ contents
+! !
+
+!CompressionStreamTest class methodsFor:'ttt'!
+
+compress:fn toFileNamed:aName
+    "
+    self compress:'symbols.stc' toFileNamed:'YYY'.
+    "
+    |sourceFile in zip out zipFile|
+
+    sourceFile := fn asFilename.
+    sourceFile exists ifFalse:[self error].
+
+    zipFile := aName asFilename.
+    zipFile := zipFile withSuffix:'gz'.
+    zipFile exists ifTrue:[ zipFile remove ].
+
+    in  := sourceFile readStream.
+    out := FileStream newFileNamed:zipFile.
+
+    [ 
+        in  := sourceFile readStream.
+        in binary.
+        out := FileStream newFileNamed:zipFile.
+        out binary.
+        zip := ZipStream writeOpenOn:out.
+        zip binary.
+
+        [in atEnd] whileFalse:[ |buf|
+            buf := in nextAvailable:512.
+            buf do:[:n|
+                zip nextPut:n
+            ]
+        ].
+    ] ensure:[
+        zip notNil ifTrue:[ zip close ].
+        in  notNil ifTrue:[ in  close ].
+        out notNil ifTrue:[ out close ].
+
+    ].
+    ^ zipFile
+!
+
+test
+"
+self test
+"
+    |zipFile srcFile oldContents newContents s|
+
+    srcFile := 'symbols.stc' asFilename.
+    zipFile := 'YYY'.
+
+    self compress:srcFile toFileNamed:zipFile.
+    newContents := self uncompressFileNamed:zipFile.
+    oldContents := srcFile binaryContentsOfEntireFile asString.
+    newContents := newContents asString.
+
+    oldContents keysAndValuesDo:[:i :v|
+        s := newContents at:i ifAbsent:nil.
+        v = s ifFalse:[
+            Transcript showCR:'#ERROR#'.
+self halt.
+            ^ self
+        ].
+        Transcript show:v.
+    ].
+    self halt.
+!
+
+uncompressFileNamed:aName
+    "
+    self uncompressFileNamed:'YYY'
+    "
+    |stream zipFile zipStream outStream c|
+
+    zipFile := aName asFilename.
+    zipFile := zipFile withSuffix:'gz'.
+
+    zipFile exists ifFalse:[ self error ].
+
+    [
+        stream    := zipFile readStream.
+        stream binary.
+
+        zipStream := ZipStream readOpenOn:stream.
+        zipStream binary.
+
+        outStream := #[] writeStream.
+
+        [ (c := zipStream next) notNil ] whileTrue:[
+            outStream nextPut:c
+        ].
+    ] ensure:[
+        zipStream notNil ifTrue:[zipStream close].
+        stream    notNil ifTrue:[stream close].
+    ]. 
+    ^ outStream contents
+! !
+
+!CompressionStreamTest methodsFor:'helpers'!
+
+doTest01:compressionStreamClass
+    "
+     ZipStream test
+     self test01_ZipStream
+    "
+   |original compressed contents in out zip|
+
+   original := 'smalltalk.rc' asFilename contentsOfEntireFile.
+
+   in := original readStream.
+
+   [ |b|
+        out := WriteStream on:(ByteArray new:10).
+        zip := compressionStreamClass writeOpenOn:out.
+
+        [in atEnd] whileFalse:[
+            zip nextPut:in next
+        ]
+   ] ensure:[ zip notNil ifTrue:[ zip close ] ].
+
+   compressed := out contents.
+   [ |b|
+        zip := compressionStreamClass readOpenOn:(compressed readStream).
+        out := String writeStream.
+
+        [ (b := zip next) notNil ] whileTrue:[ out nextPut:b ]
+
+   ] ensure:[
+        zip notNil ifTrue:[ zip close ].
+        contents := out contents.
+
+        Transcript showCR:(contents   size).
+        Transcript showCR:(compressed size).
+   ].
+
+   original = contents ifFalse:[
+        self error:'contents differs'.
+        ^ self
+   ].
+   Transcript showCR:'OK'.
+! !
+
+!CompressionStreamTest methodsFor:'tests'!
+
+test01_ZipStream
+    "
+     ZipStream test
+     self test01_ZipStream
+    "
+   self doTest01:ZipStream
+!
+
+test02_ZipStream
+    "
+     ZipStream testFile
+    "
+   |fileContents in zip out gzipCmd|
+
+   fileContents := 'smalltalk.rc' asFilename contentsOfEntireFile.
+
+   in  := fileContents readStream.
+   out := FileStream newFileNamed:'YYY.gz'.
+   out ifNil:[ ^ self ].
+
+   [ 
+      zip := ZipStream writeOpenOn:out.
+
+     [in atEnd] whileFalse:[ |buf|
+        buf := in nextAvailable:512.
+        buf do:[:n|
+            zip nextPut:n
+        ]
+     ].
+   ] ensure:[
+        zip notNil ifTrue:[ zip close ].
+        out close.
+   ].
+   gzipCmd := 'gzip -dc YYY.gz > YYY; diff YYY smalltalk.rc'.
+
+   Transcript showCR:gzipCmd.
+   gzipCmd printCR.
+!
+
+test03_ZipStream_testUnixAgainstClass
+    "
+     CompressionStream doTestUnixAgainstClass
+    "
+   |stream time file zipCont cmdCont|
+
+   file := '/boot/vmlinuz' asFilename.
+   file isReadable ifFalse:[^ self error:'not existant'].
+
+   time := Time millisecondsToRun:[ |zipStream|
+        zipStream := stream := zipCont := nil.
+        [
+            stream    := file readStream.
+            zipStream := BZip2Stream readOpenOn:stream.
+            zipCont   := zipStream contents.
+        ] ensure:[
+            zipStream notNil ifTrue:[zipStream close].
+            stream    notNil ifTrue:[stream close].
+        ].
+   ].
+   Transcript showCR:('STX   Time : %1  Size: %2' bindWith:time with:(zipCont size)).
+
+   time := Time millisecondsToRun:[ |command|
+        cmdCont := stream := nil.
+        [
+            command := 'gunzip < ' , file pathName.
+            stream  := PipeStream readingFrom:command.
+            cmdCont := stream contentsOfEntireFile.
+
+        ] ensure:[
+            stream notNil ifTrue:[stream close].
+        ]
+   ].
+   Transcript showCR:('UNIX  Time : %1  Size: %2' bindWith:time with:(cmdCont size)).
+
+   cmdCont = zipCont ifTrue:[ Transcript showCR:'OK' ]
+                    ifFalse:[ self error:'contents differs' ].
+!
+
+test04_ZipStream_NextN
+    "
+        CompressionStream doTestNextN
+    "
+   |stream time file zipCont nxtCont|
+
+   file := '/boot/vmlinuz' asFilename.
+   file isReadable ifFalse:[^ self error:'not existant'].
+
+   time := Time millisecondsToRun:[ |zipStream|
+        zipStream := stream := zipCont := nil.
+        [
+            stream    := file readStream.
+            zipStream := BZip2Stream readOpenOn:stream.
+            zipCont   := zipStream contents.
+        ] ensure:[
+            zipStream notNil ifTrue:[zipStream close].
+            stream    notNil ifTrue:[stream close].
+        ].
+   ].
+   Transcript showCR:('STX   Time : %1  Size: %2' bindWith:time with:(zipCont size)).
+
+   time := Time millisecondsToRun:[ |zipStream wstream|
+        zipStream := stream := nxtCont := nil.
+        [
+            stream    := file readStream.
+            wstream   := String writeStream.
+            zipStream := BZip2Stream readOpenOn:stream.
+
+            [zipStream atEnd] whileFalse:[
+                wstream nextPutAll:(zipStream next:117)
+            ].
+            nxtCont := wstream contents.
+        ] ensure:[
+            zipStream notNil ifTrue:[zipStream close].
+            stream    notNil ifTrue:[stream close].
+        ].
+   ].
+   Transcript showCR:('NEXT  Time : %1  Size: %2' bindWith:time with:(nxtCont size)).
+
+   nxtCont = zipCont ifTrue:[ Transcript showCR:'OK' ]
+                    ifFalse:[ self error:'contents differs' ].
+!
+
+test04_ZipStream_SkipN
+"
+    CompressionStream doTestSkipN
+"
+   |stream time file skpCont nxtCont skip|
+
+   file := '/boot/vmlinuz' asFilename.
+   file isReadable ifFalse:[^ self error:'not existant'].
+
+   skip := 6885379.
+
+   time := Time millisecondsToRun:[ |zipStream wstream|
+        zipStream := stream := nxtCont := nil.
+        [
+            stream    := file readStream.
+            wstream   := String writeStream.
+            zipStream := BZip2Stream readOpenOn:stream.
+            skip timesRepeat:[ zipStream next ].
+
+            [zipStream atEnd] whileFalse:[
+                wstream nextPutAll:(zipStream next:117)
+            ].
+            nxtCont := wstream contents.
+        ] ensure:[
+            zipStream notNil ifTrue:[zipStream close].
+            stream    notNil ifTrue:[stream close].
+        ].
+   ].
+
+   Transcript showCR:('STX   Time : %1  Size: %2' bindWith:time with:(nxtCont size)).
+
+   time := Time millisecondsToRun:[ |zipStream wstream|
+        zipStream := stream := skpCont := nil.
+        [
+            stream    := file readStream.
+            wstream   := '' writeStream.
+            zipStream := BZip2Stream readOpenOn:stream.
+            zipStream skip:skip.
+            [zipStream atEnd] whileFalse:[
+                wstream nextPutAll:(zipStream next:117)
+            ].
+            skpCont := wstream contents.
+        ] ensure:[
+            zipStream notNil ifTrue:[zipStream close].
+            stream    notNil ifTrue:[stream close].
+        ].
+   ].
+   Transcript showCR:('NEXT  Time : %1  Size: %2' bindWith:time with:(skpCont size)).
+
+   nxtCont = skpCont ifTrue:[ Transcript showCR:'OK' ]
+                    ifFalse:[ self error:'contents differs' ].
+! !
+
+!CompressionStreamTest class methodsFor:'documentation'!
+
+version
+    ^ '$Header$'
+!
+
+version_CVS
+    ^ '$Header$'
+! !
+