*** empty log message ***
authorca
Tue, 25 Jun 2002 10:27:34 +0200
changeset 1059 b47e4eff5543
parent 1058 9bb0165350ab
child 1060 a59e60d44eb4
*** empty log message ***
BZip2Stream.st
CompressionStream.st
ZipStream.st
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/BZip2Stream.st	Tue Jun 25 10:27:34 2002 +0200
@@ -0,0 +1,330 @@
+"{ Package: 'ca:Compress' }"
+
+CompressionStream subclass:#BZipStream
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'A-Compress'
+!
+
+!BZipStream primitiveDefinitions!
+%{
+
+/*
+ * includes, defines, structure definitions
+ * and typedefs come here.
+ */
+
+#include "bzip/bzlib.h"
+
+typedef enum {
+          e_opmode_unspecified
+        , e_opmode_deflate
+        , e_opmode_inflate
+} e_opmode;
+
+typedef struct {
+        bz_stream       stream;
+        char *          in_ref;
+        char *          out_ref;
+        unsigned int    out_total;
+
+        e_opmode        op_mode;
+} zstream_s;
+
+%}
+! !
+
+!BZipStream methodsFor:'low level'!
+
+zclose
+    "low level close of the zip stream
+    "
+    onStream := mode := nil.
+    hitEOF   := true.
+
+    zstream ifNil:[^ self].
+    self unregisterForFinalization.
+%{
+    OBJ _zstreamObj = __INST( zstream );
+
+    if( _zstreamObj != nil )
+    {
+        zstream_s * _zstream = (zstream_s *) __externalBytesAddress( _zstreamObj );
+
+        __INST(zstream) = nil;
+
+        if( _zstream->stream.state != NULL )
+        {
+            if( _zstream->op_mode == e_opmode_inflate )
+                BZ2_bzDecompressEnd( & _zstream->stream );
+            else
+                BZ2_bzCompressEnd( & _zstream->stream );
+        }
+        free( _zstream );
+    }
+%}.
+    zstream := nil.
+!
+
+zdeflate
+    "low level - deflate
+    "
+    |errorNo|
+
+    errorNo := nil.
+
+%{
+    OBJ _zstreamObj = __INST( zstream );
+
+    if( _zstreamObj != nil )
+    {
+        int          _errorNo, _action;
+        unsigned int _bfsize;
+        zstream_s *  _zstream = (zstream_s *) __externalBytesAddress( _zstreamObj );
+
+        if( _zstream->op_mode != e_opmode_deflate )
+            RETURN( nil );
+
+        _bfsize = _zstream->out_total;
+
+        if( _zstream->stream.state == NULL )
+        {
+            _zstream->op_mode = e_opmode_unspecified;
+            RETURN( nil );
+        }
+        _action = (__INST(hitEOF) == true) ? BZ_FINISH : BZ_RUN;        
+
+        _zstream->stream.avail_out = _bfsize;
+        _zstream->stream.next_out  = _zstream->out_ref;
+        
+        _errorNo = BZ2_bzCompress( & _zstream->stream, _action );
+
+        if( _errorNo == BZ_STREAM_END )
+        {
+            _zstream->stream.avail_in = 0;
+            _zstream->stream.next_in  = NULL;
+            _errorNo = BZ2_bzCompressEnd( & _zstream->stream );
+        }
+
+        if(   (_errorNo == BZ_OK)
+           || (_errorNo == BZ_RUN_OK)
+           || (_errorNo == BZ_FINISH_OK)
+          )
+        {
+            if(   (_zstream->stream.avail_out != _bfsize)
+               || (_zstream->stream.avail_in  != 0)
+              )
+              RETURN( true );
+
+            RETURN( false );
+        }
+        errorNo = __MKSMALLINT( _errorNo );
+    }
+%}.
+    errorNo ifNil:[
+        zstream ifNil:[self errorNotOpen].
+        self invalidArguments.
+    ].
+    self zerror:errorNo.
+!
+
+zdeflateInit
+    "low level - open for reading
+    "
+    |errorNo blockSize100k workFactor|
+
+    errorNo       := nil.
+    blockSize100k := BlockSize.
+    workFactor    := 30.
+%{
+    OBJ _zstreamObj = __INST( zstream );
+
+    if( (_zstreamObj != nil) && __bothSmallInteger(blockSize100k, workFactor) )
+    {
+        int         _errorNo;
+        zstream_s * _zstream = (zstream_s *) __externalBytesAddress( _zstreamObj );
+
+        _zstream->op_mode = e_opmode_deflate;
+
+        _errorNo = BZ2_bzCompressInit( & _zstream->stream
+                                     , __intVal( blockSize100k ), 0, __intVal( workFactor ) );
+
+        if( _errorNo == BZ_OK )
+            RETURN( self );
+
+        errorNo = __MKSMALLINT( _errorNo );
+    }
+%}.
+    errorNo ifNil:[
+        zstream ifNil:[ self errorNotOpen ].
+        self invalidArguments .
+    ].
+    self zerror:errorNo.
+!
+
+zget_avail_out
+    "low level - get the number of available out bytes
+    "
+%{
+    OBJ _zstreamObj = __INST( zstream );
+
+    if( _zstreamObj != nil )
+    {
+        unsigned int _count;
+        zstream_s *  _zstream = (zstream_s *) __externalBytesAddress( _zstreamObj );
+
+        _count = _zstream->out_total - _zstream->stream.avail_out;
+
+        RETURN( __MKSMALLINT (_count) );
+    }
+%}.
+    self errorNotOpen.
+!
+
+zinflate
+    "low level - inflate
+    "
+    |errorNo|
+
+    errorNo := nil.
+%{
+    OBJ _zstreamObj = __INST( zstream );
+
+    if( _zstreamObj != nil )
+    {
+        int         _errorNo, _count;
+        zstream_s * _zstream;
+
+        _zstream = (zstream_s *) __externalBytesAddress( _zstreamObj );
+
+        if( _zstream->op_mode != e_opmode_inflate )
+            RETURN( nil );
+
+        if( _zstream->stream.state == NULL )
+        {
+            _zstream->op_mode = e_opmode_unspecified;
+            RETURN( nil );
+        }
+        if( _zstream->stream.avail_in == 0 )
+            RETURN( __MKSMALLINT (0) );
+
+        _zstream->stream.avail_out = _zstream->out_total;
+        _zstream->stream.next_out  = _zstream->out_ref;
+
+        _errorNo = BZ2_bzDecompress( & _zstream->stream );
+
+        if( _errorNo == BZ_STREAM_END )
+            _errorNo = BZ2_bzDecompressEnd( & _zstream->stream );
+
+        if( _errorNo == BZ_OK )
+        {
+            _count = _zstream->out_total - _zstream->stream.avail_out;
+
+            RETURN( __MKSMALLINT (_count) );
+        }
+        errorNo = __MKSMALLINT( _errorNo );
+    }
+%}.
+    errorNo ifNil:[ self errorNotOpen ].
+    self zerror:errorNo.
+!
+
+zinflateInit
+    "low level - inflateInit
+    "
+    |errorNo|
+
+    errorNo := nil.
+
+%{
+    OBJ _zstreamObj = __INST( zstream );
+
+    if( _zstreamObj != nil )
+    {
+        int         _errorNo;
+        zstream_s * _zstream = (zstream_s *) __externalBytesAddress( _zstreamObj );
+
+        _zstream->op_mode = e_opmode_inflate;
+        _errorNo = BZ2_bzDecompressInit( & _zstream->stream, 0, 1 );
+
+        if( _errorNo == BZ_OK )
+            RETURN( self );
+
+        _zstream->stream.avail_in = 0;
+        errorNo = __MKSMALLINT( _errorNo );
+    }
+%}.
+    errorNo ifNil:[ self errorNotOpen ].
+    self zerror:errorNo.
+!
+
+zopen
+    "low level - opens the zip stream
+    "
+    |outTotal|
+
+    outTotal := outputBytes size.
+%{
+    zstream_s * _zstream = (zstream_s *) malloc( sizeof(zstream_s) );
+
+    if( _zstream )
+    {
+        OBJ     _zobj   = __MKEXTERNALADDRESS( _zstream );
+        OBJ     _outObj = __INST( outputBytes );
+        OBJ     _inpObj = __INST( inputBytes  );
+
+        _zstream->in_ref           = (char *) __externalBytesAddress( _inpObj );
+        _zstream->stream.next_in   = NULL;
+        _zstream->stream.avail_in  = 0;
+        _zstream->stream.total_in_lo32  = 0;
+        _zstream->stream.total_in_hi32  = 0;
+
+        _zstream->out_total        = __intVal( outTotal );
+        _zstream->out_ref          = (char *) __externalBytesAddress( _outObj );
+        _zstream->stream.next_out  = _zstream->out_ref;
+        _zstream->stream.avail_out = _zstream->out_total;
+
+        _zstream->stream.total_out_lo32 = 0;
+        _zstream->stream.total_out_hi32 = 0;
+
+        _zstream->stream.bzalloc   = 0;
+        _zstream->stream.bzfree    = 0;
+        _zstream->stream.opaque    = 0;
+
+        _zstream->op_mode          = e_opmode_unspecified;
+
+        __INST (zstream) = _zobj;
+        __STORE(self, _zobj);
+    }
+%}.
+!
+
+zset_avail_in:count
+    "set the 'avail_in' and compute the crc
+    "
+%{
+    OBJ _zstreamObj = __INST( zstream );
+
+    if( (_zstreamObj != nil) && __isSmallInteger(count) )
+    {
+        int         _count;
+        zstream_s * _zstream = (zstream_s *) __externalBytesAddress( _zstreamObj );
+
+        if( (_count = __intVal( count )) > 0 )
+        {
+            char * _in_ref = _zstream->in_ref;
+
+            _zstream->stream.avail_in = _count;
+            _zstream->stream.next_in  = _in_ref;
+        } else {
+            _zstream->stream.avail_in = 0;
+            _zstream->stream.next_in  = NULL;
+        }
+        RETURN( self );
+    }
+%}.
+    zstream ifNil:[ self errorNotOpen ].
+    self invalidArguments.
+! !
+
--- /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!
--- a/ZipStream.st	Tue Jun 25 07:14:46 2002 +0200
+++ b/ZipStream.st	Tue Jun 25 10:27:34 2002 +0200
@@ -2,14 +2,12 @@
 
 "{ Package: 'ca:Compress' }"
 
-Stream subclass:#ZipStream
-        instanceVariableNames:'onStream hitEOF binary position readLimit mode inputBytes outputBytes zstream'
-        classVariableNames:'Z_DEFLATED Z_DEFAULT_COMPRESSION Z_DEFAULT_LEVEL Z_BEST_COMPRESSION
-                Z_DEF_MEM_LEVEL Z_DEFAULT_STRATEGY Z_FILTERED Z_HUFFMAN_ONLY
-                HEAD_OS_CODE HEAD_RESERVED HEAD_EXTRA_FIELD HEAD_ORIG_NAME
-                HEAD_COMMENT HEAD_CRC GZ_MAGIC_ID'
-        poolDictionaries:''
-        category:'A-Compress'
+CompressionStream subclass:#ZipStream
+	instanceVariableNames:''
+	classVariableNames:'Z_DEFLATED HEAD_OS_CODE HEAD_RESERVED HEAD_EXTRA_FIELD
+		HEAD_ORIG_NAME HEAD_COMMENT HEAD_CRC GZ_MAGIC_ID'
+	poolDictionaries:''
+	category:'A-Compress'
 !
 
 !ZipStream primitiveDefinitions!
@@ -46,39 +44,15 @@
 !ZipStream class methodsFor:'initialization'!
 
 initialize
-    |varZ_DEFLATED
-     varZ_DEFAULT_COMPRESSION varZ_BEST_COMPRESSION  varZ_DEF_MEM_LEVEL
-     varZ_DEFAULT_STRATEGY varZ_FILTERED varZ_HUFFMAN_ONLY
-     varHEAD_OS_CODE
-    |
+    |z_deflated os_code|
 %{
-    varZ_DEFLATED            = __MKSMALLINT( Z_DEFLATED );
-
-    varZ_DEFAULT_COMPRESSION = __MKSMALLINT( Z_DEFAULT_COMPRESSION );
-    varZ_BEST_COMPRESSION    = __MKSMALLINT( Z_BEST_COMPRESSION  );
-
-    varZ_DEF_MEM_LEVEL       = __MKSMALLINT( DEF_MEM_LEVEL );
-
-    varZ_DEFAULT_STRATEGY    = __MKSMALLINT( Z_DEFAULT_STRATEGY );
-    varZ_FILTERED            = __MKSMALLINT( Z_FILTERED );
-    varZ_HUFFMAN_ONLY        = __MKSMALLINT( Z_HUFFMAN_ONLY );
-    varHEAD_OS_CODE          = __MKSMALLINT( OS_CODE );
+    z_deflated = __MKSMALLINT( Z_DEFLATED );
+    os_code    = __MKSMALLINT( OS_CODE );
 %}.
 
-    Z_DEFLATED            := varZ_DEFLATED.
-
-    Z_DEFAULT_COMPRESSION := varZ_DEFAULT_COMPRESSION.
-    Z_DEFAULT_LEVEL       := 6.
-    Z_BEST_COMPRESSION    := varZ_BEST_COMPRESSION.
+    Z_DEFLATED            := z_deflated.
 
-    Z_DEF_MEM_LEVEL       := varZ_DEF_MEM_LEVEL.
-
-    Z_DEFAULT_STRATEGY    := varZ_DEFAULT_STRATEGY.
-    Z_FILTERED            := varZ_FILTERED.
-    Z_HUFFMAN_ONLY        := varZ_HUFFMAN_ONLY.
-
-    HEAD_OS_CODE          := varHEAD_OS_CODE.
-
+    HEAD_OS_CODE          := os_code.
     HEAD_RESERVED         := 16rE0.     " bits 5..7:  reserved "
     HEAD_EXTRA_FIELD      := 16r04.     " bit 2 set:  extra field present "
     HEAD_ORIG_NAME        := 16r08.     " bit 3 set:  original file name present "
@@ -89,243 +63,8 @@
 
 ! !
 
-!ZipStream class methodsFor:'instance creation'!
-
-readOpenOn:aStream
-    "read data from an compressed stream
-    "
-    ^ self basicNew readOpenOn:aStream
-!
-
-writeOpenOn:aStream
-    "write data compressed to stream 
-    "
-    ^ self writeOpenOn:aStream level:Z_DEFAULT_LEVEL
-                            memLevel:Z_DEF_MEM_LEVEL
-                            strategy:Z_DEFAULT_STRATEGY.
-!
-
-writeOpenOn:aStream level:level memLevel:memLevel strategy:strategy
-    "write data compressed to stream
-     The memLevel level specifies the compression level used; 0 means write
-     out uncompressed, a higher number results in better compression
-
-     The memLevel parameter specifies how much memory should be allocated
-     for the internal compression state. memLevel=1 uses minimum memory but
-     is slow and reduces compression ratio; memLevel=9 uses maximum memory
-     for optimal speed. The default value is 8.
-
-     The strategy parameter is used to tune the compression algorithm. Use the
-     value Z_DEFAULT_STRATEGY for normal data, Z_FILTERED for data produced by a
-     filter (or predictor), or Z_HUFFMAN_ONLY to force Huffman encoding only (no
-     string match). Filtered data consists mostly of small values with a
-     somewhat random distribution. In this case, the compression algorithm is
-     tuned to compress them better. The effect of Z_FILTERED is to force more
-     Huffman coding and less string matching; it is somewhat intermediate
-     between Z_DEFAULT and Z_HUFFMAN_ONLY. The strategy parameter only affects
-     the compression ratio but not the correctness of the compressed output even
-     if it is not set appropriately.
-    "
-    |z|
-
-    z := self basicNew.
-    z writeOpenOn:aStream level:level memLevel:memLevel strategy:strategy.
-  ^ z
-! !
-
-!ZipStream class methodsFor:'test'!
-
-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:[
-            (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
-"
-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
-        ]
-     ].
-   ] valueNowOrOnUnwindDo:[
-        zip ifNotNil:[ zip close ].
-        out close.
-   ].
-   gzipCmd := 'gzip -dc YYY.gz > YYY; diff YYY smalltalk.rc'.
-
-   Transcript showCR:gzipCmd.
-   gzipCmd printCR.
-! !
-
-!ZipStream methodsFor:'accessing'!
-
-binary
-    "switch to binary mode - default is text
-    "
-    binary := true.
-!
-
-text
-    "switch to text mode - default is text
-    "
-    binary := false.
-! !
-
-!ZipStream 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).
-! !
-
-!ZipStream 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.
-! !
-
 !ZipStream methodsFor:'low level'!
 
-zset_avail_in:count
-    "set the 'avail_in' and compute the crc
-    "
-%{
-    OBJ _zstreamObj = __INST( zstream );
-
-    if( (_zstreamObj != nil) && __isSmallInteger(count) )
-    {
-        int         _count;
-        zstream_s * _zstream = (zstream_s *) __externalBytesAddress( _zstreamObj );
-
-        if( (_count = __intVal( count )) > 0 )
-        {
-            Bytef * _in_ref = _zstream->in_ref;
-
-            _zstream->stream.avail_in = _count;
-            _zstream->stream.next_in  = _in_ref;
-
-            if( _zstream->op_mode == e_opmode_deflate )
-                _zstream->crc_32 = crc32( _zstream->crc_32, _in_ref, _count );
-        } else {
-            _zstream->stream.avail_in = 0;
-            _zstream->stream.next_in  = Z_NULL;
-        }
-        RETURN( self );
-    }
-%}.
-    zstream ifNil:[ self errorNotOpen ].
-    self invalidArguments.
-!
-
 zclose
     "low level close of the zip stream
     "
@@ -428,21 +167,17 @@
     self zerror:errorNo.
 !
 
-zdeflateInit:aLevel memLevel:memLevel strategy:strategy
+zdeflateInit
     "low level - deflateInit
     "
-    |errorNo|
+    |errorNo level|
 
     errorNo := nil.
-
+    level   := BlockSize.
 %{
     OBJ _zstreamObj = __INST( zstream );
 
-    if(   (_zstreamObj != nil)
-       && __isSmallInteger(aLevel)
-       && __isSmallInteger(memLevel)
-       && __isSmallInteger(strategy)
-      )
+    if( (_zstreamObj != nil) && __isSmallInteger(level) )
     {
         int         _errorNo;
         zstream_s * _zstream = (zstream_s *) __externalBytesAddress( _zstreamObj );
@@ -450,11 +185,11 @@
         _zstream->op_mode = e_opmode_deflate;
 
         _errorNo = deflateInit2( & _zstream->stream
-                               , __intVal( aLevel )
+                               , __intVal( level )
                                , Z_DEFLATED
                                , -MAX_WBITS
-                               , __intVal( memLevel )
-                               , __intVal( strategy )
+                               , DEF_MEM_LEVEL
+                               , Z_DEFAULT_STRATEGY
                                );
 
         if( _errorNo == Z_OK )
@@ -470,6 +205,25 @@
     self zerror:errorNo.
 !
 
+zget_avail_out
+    "low level - get the number of available out bytes
+    "
+%{
+    OBJ _zstreamObj = __INST( zstream );
+
+    if( _zstreamObj != nil )
+    {
+        uInt        _count;
+        zstream_s * _zstream = (zstream_s *) __externalBytesAddress( _zstreamObj );
+
+        _count = _zstream->out_total - _zstream->stream.avail_out;
+
+        RETURN( __MKSMALLINT (_count) );
+    }
+%}.
+    self errorNotOpen.
+!
+
 zinflate
     "low level - inflate
     "
@@ -524,25 +278,6 @@
     self zerror:errorNo.
 !
 
-zget_avail_out
-    "low level - get the number of available out bytes
-    "
-%{
-    OBJ _zstreamObj = __INST( zstream );
-
-    if( _zstreamObj != nil )
-    {
-        uInt        _count;
-        zstream_s * _zstream = (zstream_s *) __externalBytesAddress( _zstreamObj );
-
-        _count = _zstream->out_total - _zstream->stream.avail_out;
-
-        RETURN( __MKSMALLINT (_count) );
-    }
-%}.
-    self errorNotOpen.
-!
-
 zinflateInit
     "low level - inflateInit
     "
@@ -572,18 +307,12 @@
     self zerror:errorNo.
 !
 
-zopen:aStream
+zopen
     "low level - opens the zip stream
     "
     |outTotal|
 
-    (onStream := aStream) ifNil:[ self errorNotOpen ].
-
-    outputBytes := ExternalBytes unprotectedNew:8192.
-    inputBytes  := ExternalBytes unprotectedNew:8192.
-    outTotal    := outputBytes size.
-    readLimit   := position := 0.
-    binary      := false.
+    outTotal := outputBytes size.
 %{
     zstream_s * _zstream = (zstream_s *) malloc( sizeof(zstream_s) );
 
@@ -617,294 +346,105 @@
         __STORE(self, _zobj);
     }
 %}.
-    zstream ifNil:[ self zerror:'cannot allocate zbuffer' ].
-    hitEOF := false.
-    self registerForFinalization.
-! !
-
-!ZipStream methodsFor:'private'!
-
-onStreamPutBytes:count from:data
-    "write compressed data to the (output) stream
-    "
-    onStream ifNil:[ self errorNotOpen ].
-    onStream nextPutBytes:count from:data startingAt:1
-! !
-
-!ZipStream methodsFor:'private todo'!
-
-readHeader
-    "read and validate gzip header
-    "
-    |method flags|
-
-    self isReadOpen ifFalse:[ self errorReadOnly ].
-
-    "Check the gzip magic id
-    "
-    GZ_MAGIC_ID do:[:b|
-        onStream nextByte ~~ b ifTrue:[ self zerror:'version error' ]
-    ].
-
-    method := onStream nextByte.
-    method ~~ Z_DEFLATED ifTrue:[
-        self zerror:'invalid method (not deflated)'
-    ].
-
-    flags := onStream nextByte.
-    (flags bitAnd:HEAD_RESERVED) ~~ 0 ifTrue:[
-        self zerror:'wrong data format'
-    ].
-
-    "discard time, xflags and OS code
-    "
-    onStream skip:6.
-
-    (flags bitAnd:HEAD_EXTRA_FIELD) ~~ 0 ifTrue:[|len|
-        "skip the extra field"
-        len := onStream nextByte + (onStream nextByte bitShift:8).
-        len timesRepeat:[ onStream nextByte ].
-    ].
-
-    (flags bitAnd:HEAD_ORIG_NAME) ~~ 0 ifTrue:[|b|
-        "skip the original file name"
-        Transcript show:'header name: '.
-        [ (b := onStream nextByte) ~~ 0 ] whileTrue:[
-            Transcript show:(Character value:b)
-        ].
-        Transcript cr.
-    ].
-
-    (flags bitAnd:HEAD_CRC) ~~ 0 ifTrue:[
-        "skip the header crc"
-        onStream skip:2.
-    ].
-
 !
 
-writeHeader
-    "write the gzip header
-    "
-    self isWriteOpen ifFalse:[ self errorWriteOnly ].
-
-    "write the gzip magic id
-    "
-    GZ_MAGIC_ID do:[:b| onStream nextPutByte:b ].
-
-    "write the method
-    "
-    onStream nextPutByte:Z_DEFLATED.
-
-    "write the flags
-    "
-    onStream nextPutByte:0.
-
-    "write time
-    "
-    4 timesRepeat:[ onStream nextPutByte:0 ].
-
-    "write xflags
-    "
-    onStream nextPutByte:0.
-    "write OS code
-    "
-    onStream nextPutByte:HEAD_OS_CODE.
-
-! !
-
-!ZipStream 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
+zset_avail_in:count
+    "set the 'avail_in' and compute the crc
     "
-    ^ mode == #readonly
-!
-
-isWriteOpen
-    "return true, if this stream can be written to
-    "
-    ^ mode == #writeonly
-! !
-
-!ZipStream methodsFor:'reading'!
+%{
+    OBJ _zstreamObj = __INST( zstream );
 
-contents
-    "return the entire contents of the stream
-    "
-    |out b|
-
-    mode == #readonly ifFalse:[ self errorReadOnly ].
+    if( (_zstreamObj != nil) && __isSmallInteger(count) )
+    {
+        int         _count;
+        zstream_s * _zstream = (zstream_s *) __externalBytesAddress( _zstreamObj );
 
-    out := (String new:1024) writeStream.
-
-    [ (b := self next) notNil ] whileTrue:[
-        out nextPut:b
-    ].
-    ^ out contents
-!
+        if( (_count = __intVal( count )) > 0 )
+        {
+            Bytef * _in_ref = _zstream->in_ref;
 
-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.
+            _zstream->stream.avail_in = _count;
+            _zstream->stream.next_in  = _in_ref;
 
-            (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
+            if( _zstream->op_mode == e_opmode_deflate )
+                _zstream->crc_32 = crc32( _zstream->crc_32, _in_ref, _count );
+        } else {
+            _zstream->stream.avail_in = 0;
+            _zstream->stream.next_in  = Z_NULL;
+        }
+        RETURN( self );
+    }
+%}.
+    zstream ifNil:[ self errorNotOpen ].
+    self invalidArguments.
 ! !
 
 !ZipStream methodsFor:'startup & release'!
 
-close
-    "close the zip-stream
-    "
-    hitEOF := true.
-
-    zstream ifNotNil:[
-        self flush.
-        self zclose.
-    ].
-!
+openWithMode:aMode on:aStream
+    super openWithMode:aMode on:aStream.
 
-readOpenOn:aStream
-
-    mode := #readonly.
+    self isReadOpen ifTrue:[
+        "Check the gzip magic id
+        "
+        |flags|
 
-    self zopen:aStream.
-    self zinflateInit.
-    self readHeader.
-!
-
-writeOpenOn:aStream level:level memLevel:memLevel strategy:strategy
-
-    mode := #writeonly.
+        GZ_MAGIC_ID do:[:b|
+            onStream nextByte ~~ b ifTrue:[ self zerror:'version error' ]
+        ].
 
-    self zopen:aStream.
-    self zdeflateInit:level memLevel:memLevel strategy:strategy.
-    self writeHeader.
-! !
+        onStream nextByte ~~ Z_DEFLATED ifTrue:[
+            self zerror:'invalid method (not deflated)'
+        ].
 
-!ZipStream methodsFor:'writing'!
-
-flush
-    "flush the input and output buffer
-    "
-    |continue|
+        flags := onStream nextByte.
+        (flags bitAnd:HEAD_RESERVED) ~~ 0 ifTrue:[
+            self zerror:'wrong data format'
+        ].
 
-    self isWriteOpen ifFalse:[ ^ self ].
-    self zset_avail_in:position.
-
-    position := 0.
-    continue := true.
+        "discard time, xflags and OS code"
+        onStream skip:6.
 
-    [continue] whileTrue:[ |count|
-        count := self zget_avail_out.
-
-        count > 0 ifTrue:[
-            self onStreamPutBytes:count from:outputBytes
+        (flags bitAnd:HEAD_EXTRA_FIELD) ~~ 0 ifTrue:[|len|
+            "skip the extra field"
+            len := onStream nextByte + (onStream nextByte bitShift:8).
+            len timesRepeat:[ onStream nextByte ].
         ].
-        continue := self zdeflate.
-    ].
-!        
 
-nextPut:something
-    "write the argument, something
-    "
-    |byte|
-
-    byte := nil.
-%{
-    int _bval;
+        (flags bitAnd:HEAD_ORIG_NAME) ~~ 0 ifTrue:[|b|
+            "skip the original file name"
+            [ (b := onStream nextByte) ~~ 0 ] whileTrue.
+        ].
 
-    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);
+        (flags bitAnd:HEAD_CRC) ~~ 0 ifTrue:[
+            "skip the header crc"
+            onStream skip:2.
+        ].
+    ] ifFalse:[
+        "write the gzip magic id
+        "
+        GZ_MAGIC_ID do:[:b| onStream nextPutByte:b ].
 
-            if( (_bval < 0) || (_bval > 255) )
-                goto bad;
-        }
-        else
-            goto bad;
+        "write the method"
+        onStream nextPutByte:Z_DEFLATED.
+
+        "write the flags"
+        onStream nextPutByte:0.
 
-        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.
-!
+        "write time"
+        4 timesRepeat:[ onStream nextPutByte:0 ].
 
-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.
-    ].
+        "write xflags"
+        onStream nextPutByte:0.
+
+        "write OS code"
+        onStream nextPutByte:HEAD_OS_CODE.
+    ].    
 ! !
 
 !ZipStream class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic2/ZipStream.st,v 1.14 2002-06-25 05:14:46 ca Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic2/ZipStream.st,v 1.15 2002-06-25 08:27:34 ca Exp $'
 ! !
 ZipStream initialize!