CompressionStream.st
changeset 1059 b47e4eff5543
child 1061 be824dc5e0e7
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/CompressionStream.st	Tue Jun 25 10:27:34 2002 +0200
@@ -0,0 +1,444 @@
+"{ Package: 'ca:Compress' }"
+
+Stream subclass:#CompressionStream
+	instanceVariableNames:'onStream hitEOF binary position readLimit mode inputBytes
+		outputBytes zstream'
+	classVariableNames:'BlockSize'
+	poolDictionaries:''
+	category:'A-Compress'
+!
+
+!CompressionStream class methodsFor:'initialization'!
+
+initialize
+    BlockSize := 6.
+! !
+
+!CompressionStream class methodsFor:'instance creation'!
+
+readOpenOn:aStream
+    "read data from an compressed stream
+    "
+    ^ self basicNew openWithMode:#readonly on:aStream
+!
+
+writeOpenOn:aStream
+    "write data compressed to stream 
+    "
+    ^ self basicNew openWithMode:#writeonly on:aStream
+! !
+
+!CompressionStream class methodsFor:'test'!
+
+test
+"
+CompressionStream 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:[
+            (b := in next) ifNotNil:[zip nextPut:b]
+        ]
+   ] valueNowOrOnUnwindDo:[ zip ifNotNil:[ zip close ] ].
+
+   compressed := out contents.
+   [ |b|
+        zip := self readOpenOn:(compressed readStream).
+        out := '' writeStream.
+
+        [ (b := zip next) notNil ] whileTrue:[ out nextPut:b ]
+
+   ] valueNowOrOnUnwindDo:[
+        zip ifNotNil:[ zip close ].
+        contents := out contents.
+
+        Transcript showCR:(contents   size).
+        Transcript showCR:(compressed size).
+   ].
+
+   original = contents ifFalse:[
+        self halt:'contents differs'.
+      ^ self
+   ].
+   Transcript showCR:'OK'.
+!
+
+testFile
+"
+CompressionStream 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
+        ]
+     ].
+   ] valueNowOrOnUnwindDo:[
+        zip ifNotNil:[ zip close ].
+        out close.
+   ].
+   gzipCmd := 'gzip -dc YYY.gz > YYY; diff YYY smalltalk.rc'.
+
+   Transcript showCR:gzipCmd.
+   gzipCmd printCR.
+! !
+
+!CompressionStream methodsFor:'accessing'!
+
+binary
+    "switch to binary mode - default is text
+    "
+    binary := true.
+!
+
+text
+    "switch to text mode - default is text
+    "
+    binary := false.
+! !
+
+!CompressionStream methodsFor:'error handling'!
+
+errorNotOpen
+    "report an error, that the stream has not been opened
+    "
+    self zerror:'not open'.
+!
+
+errorReadOnly
+    "report an error, that the stream is a readOnly stream
+    "
+    self zerror:'is readonly'
+!
+
+errorWriteOnly
+    "report an error, that the stream is a writeOnly stream
+    "
+    self zerror:'is writeonly'
+!
+
+invalidArgument
+    "called if a method is invoked with invalid parameters.
+    "
+    self zerror:'invalid arguments'.
+!
+
+pastEnd
+    self zerror:'end of stream'.
+!
+
+zerror:anError
+    |error|
+
+    zstream isNil ifTrue:[
+        error := 'not open'.
+    ] ifFalse:[
+        anError isNumber ifTrue:[
+                     anError ==  1 ifTrue:[ error := 'stream at end' ]
+            ifFalse:[anError == -1 ifTrue:[ error := 'processing error: ', anError printString ]
+            ifFalse:[anError == -2 ifTrue:[ error := 'processing error' ]
+            ifFalse:[anError == -3 ifTrue:[ error := 'input data are corrupted' ]
+            ifFalse:[anError == -4 ifTrue:[ error := 'not enough memory' ]
+            ifFalse:[anError == -5 ifTrue:[ error := 'not enough memory in the output stream' ]
+            ifFalse:[anError == -6 ifTrue:[ error := 'version error' ]
+            ifFalse:[
+                    error := 'compressing error: ', anError printString                
+            ]]]]]]].
+        ] ifFalse:[
+            error := anError printString
+        ].
+    ].
+    self zclose.
+    Stream streamErrorSignal raiseErrorString:(self class name , ': ', error).
+! !
+
+!CompressionStream methodsFor:'finalization'!
+
+executor
+    "redefined to return a lightweight copy 
+     - all we need is the memory handle.
+    "
+    ^ self class basicNew finalizeCopy:zstream.    
+!
+
+finalize
+    self zclose.
+    zstream := nil.
+!
+
+finalizeCopy:aZStream
+    zstream := aZStream.
+! !
+
+!CompressionStream methodsFor:'low level'!
+
+zclose
+    "low level close of the zip stream
+    "
+    ^ self subclassResponsibility
+!
+
+zdeflate
+    "low level - deflate
+    "
+    ^ self subclassResponsibility
+!
+
+zdeflateInit
+    "low level - deflateInit
+    "
+    ^ self subclassResponsibility
+!
+
+zget_avail_out
+    "low level - get the number of available out bytes
+    "
+    ^ self subclassResponsibility
+!
+
+zinflate
+    "low level - inflate
+    "
+    ^ self subclassResponsibility
+!
+
+zinflateInit
+    "low level - inflateInit
+    "
+    ^ self subclassResponsibility
+!
+
+zopen
+    "low level - opens the zip stream
+    "
+    ^ self subclassResponsibility
+!
+
+zset_avail_in:count
+    "set the 'avail_in' and compute the crc
+    "
+    ^ self subclassResponsibility
+! !
+
+!CompressionStream methodsFor:'private'!
+
+onStreamPutBytes:count from:data
+    "write compressed data to the (output) stream
+    "
+    onStream ifNil:[ self errorNotOpen ].
+    onStream nextPutBytes:count from:data startingAt:1
+! !
+
+!CompressionStream methodsFor:'queries'!
+
+atEnd
+    "return true if the end of the compressed input stream has been reached
+    "
+    ^ hitEOF ~~ false
+!
+
+isBinary
+    "return true, if the stream is in binary (as opposed to text-) mode.
+     The default when created is false.
+    "
+    ^ binary
+!
+
+isOpen
+    "return true, if this stream is open
+    "
+    ^ onStream notNil
+!
+
+isReadOpen
+    "return true, if this stream can be read from
+    "
+    ^ mode == #readonly
+!
+
+isWriteOpen
+    "return true, if this stream can be written to
+    "
+    ^ mode == #writeonly
+! !
+
+!CompressionStream methodsFor:'reading'!
+
+contents
+    "return the entire contents of the stream
+    "
+    |out b|
+
+    mode == #readonly ifFalse:[ self errorReadOnly ].
+
+    out := (String new:1024) writeStream.
+
+    [ (b := self next) notNil ] whileTrue:[
+        out nextPut:b
+    ].
+    ^ out contents
+!
+
+next
+    "return the next element, a character or byte (textmode)
+     if there is  more element, nil is returned
+    "
+    |byte|
+
+    mode == #readonly ifFalse:[ self errorReadOnly ].
+
+    hitEOF == true ifTrue:[^ nil].
+
+    position == readLimit ifTrue:[
+        [ (readLimit := self zinflate) == 0 ] whileTrue:[ |n|
+            n := onStream nextBytes:(inputBytes size) into:inputBytes startingAt:1.
+
+            (n notNil and:[n > 0]) ifFalse:[
+                self pastEnd
+            ].
+            self zset_avail_in:n.
+        ].
+        readLimit ifNil:[
+            hitEOF := true.
+          ^ nil
+        ].
+        position := 0.
+    ].
+    position := position + 1.
+    byte := outputBytes at:position.
+
+    binary ifTrue:[^ byte ].
+  ^ Character value:byte
+! !
+
+!CompressionStream methodsFor:'startup & release'!
+
+close
+    "close the zip-stream
+    "
+    hitEOF := true.
+
+    zstream ifNotNil:[
+        self flush.
+        self zclose.
+    ].
+!
+
+openWithMode:aMode on:aStream
+
+    (onStream := aStream) ifNil:[ self errorNotOpen ].
+
+    mode        := aMode.
+    outputBytes := ExternalBytes unprotectedNew:8192.
+    inputBytes  := ExternalBytes unprotectedNew:8192.
+    readLimit   := position := 0.
+    binary      := false.
+
+    self zopen.
+    self registerForFinalization.
+
+    hitEOF := false.
+
+    aMode == #readonly ifTrue:[
+        self zinflateInit.
+    ] ifFalse:[
+        self zdeflateInit
+    ].
+! !
+
+!CompressionStream methodsFor:'writing'!
+
+flush
+    "flush the input and output buffer
+    "
+    |continue|
+
+    self isWriteOpen ifFalse:[ ^ self ].
+    self zset_avail_in:position.
+
+    position := 0.
+    continue := true.
+
+    [continue] whileTrue:[ |count|
+        count := self zget_avail_out.
+
+        count > 0 ifTrue:[
+            self onStreamPutBytes:count from:outputBytes
+        ].
+        continue := self zdeflate.
+    ].
+!
+
+nextPut:something
+    "write the argument, something
+    "
+    |byte|
+
+    byte := nil.
+%{
+    int _bval;
+
+    if( __INST(mode) == @symbol(writeonly) )
+    {
+        if( __INST(binary) != true )
+        {
+            if( ! __isCharacter(something) )
+                goto bad;
+
+            _bval = __intVal(__characterVal(something)) & 0xFF;
+        }
+        else if( __isSmallInteger(something) )
+        {
+            _bval = __intVal(something);
+
+            if( (_bval < 0) || (_bval > 255) )
+                goto bad;
+        }
+        else
+            goto bad;
+
+        byte = __MKSMALLINT( _bval );
+    }
+bad: ;
+%}.
+    byte ifNil:[
+        mode == #readonly ifTrue:[self errorReadOnly].
+        zstream ifNil:[ self errorNotOpen ].
+        self invalidArguments.
+    ].
+    position == inputBytes size ifTrue:[ self flush ].
+    position := position + 1.
+    inputBytes at:position put:byte.
+!
+
+nextPutByte:aByte
+    "write a byte; works in both binary and text modes.
+    "
+    binary ifTrue:[
+        self nextPut:aByte.
+    ] ifFalse:[
+        binary := true.
+        self nextPut:aByte.
+        binary := false.
+    ].
+! !
+
+CompressionStream initialize!