CompressionStream.st
changeset 1428 c9f7ec7d0c84
parent 1308 d7bea6d0b3b6
child 1446 c59e6816f4b8
--- a/CompressionStream.st	Wed Mar 17 17:14:27 2004 +0100
+++ b/CompressionStream.st	Wed Mar 17 17:14:44 2004 +0100
@@ -72,216 +72,6 @@
     ^ self basicNew openWithMode:#writeonly on:aStream
 ! !
 
-!CompressionStream class methodsFor:'test'!
-
-doTestNextN
-"
-    CompressionStream doTestNextN
-"
-   |stream time file zipCont nxtCont|
-
-   file := '/phys/exept/tmp/yyy/201--T22--D.20000415.SAGSA.DE0220523.gz' asFilename.
-   file isReadable ifFalse:[^ self error:'not existant'].
-
-   time := Time millisecondsToRun:[ |zipStream|
-        zipStream := stream := zipCont := nil.
-        [
-            stream    := file readStream.
-            zipStream := ZipStream 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   := '' writeStream.
-            zipStream := ZipStream 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' ].
-!
-
-doTestSkipN
-"
-    CompressionStream doTestSkipN
-"
-   |stream time file skpCont nxtCont skip|
-
-   file := '/phys/exept/tmp/yyy/201--T22--D.20000415.SAGSA.DE0220523.gz' asFilename.
-   file isReadable ifFalse:[^ self error:'not existant'].
-
-   skip := 6885379.
-
-   time := Time millisecondsToRun:[ |zipStream wstream|
-        zipStream := stream := nxtCont := nil.
-        [
-            stream    := file readStream.
-            wstream   := '' writeStream.
-            zipStream := ZipStream 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 := ZipStream 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' ].
-!
-
-doTestUnixAgainstClass
-"
-    CompressionStream doTestUnixAgainstClass
-"
-   |stream time file zipCont cmdCont|
-
-   file := '/phys/exept/tmp/yyy/201--T22--D.20000415.SAGSA.DE0220523.gz' asFilename.
-   file isReadable ifFalse:[^ self error:'not existant'].
-
-   time := Time millisecondsToRun:[ |zipStream|
-        zipStream := stream := zipCont := nil.
-        [
-            stream    := file readStream.
-            zipStream := ZipStream 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' ].
-!
-
-test
-"
-ZipStream test
-"
-   |original compressed contents in out zip|
-
-   original := 'smalltalk.rc' asFilename contentsOfEntireFile.
-
-   in := original readStream.
-
-   [ |b|
-        out := #[] writeStream.
-        zip := self writeOpenOn:out.
-
-        [in atEnd] whileFalse:[
-            zip nextPut:in next
-        ]
-   ] ensure:[ zip notNil ifTrue:[ zip close ] ].
-
-   compressed := out contents.
-   [ |b|
-        zip := self readOpenOn:(compressed readStream).
-        out := '' 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'.
-!
-
-testFile
-"
-ZipStream testFile
-"
-   |fileContents in zip out gzipCmd|
-
-   fileContents := 'smalltalk.rc' asFilename contentsOfEntireFile.
-
-   in  := fileContents readStream.
-   out := FileStream newFileNamed:'YYY.gz'.
-   out ifNil:[ ^ self ].
-
-   [ 
-      zip := self 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.
-! !
-
 !CompressionStream methodsFor:'accessing'!
 
 binary
@@ -586,7 +376,7 @@
 
     species := self contentsSpecies.
     buffer  := species new:bfsize.
-    stream  := (species new:bfsize) writeStream.
+    stream  := WriteStream on:(species new:bfsize).
 
     [self canReadWithoutBlocking] whileTrue:[
         count := self z_nextAvailableInto:buffer startingAt:1.
@@ -752,7 +542,7 @@
 !CompressionStream class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic2/CompressionStream.st,v 1.14 2003-08-29 19:31:31 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic2/CompressionStream.st,v 1.15 2004-03-17 16:14:44 cg Exp $'
 ! !
 
 CompressionStream initialize!