ZipStream.st
author ca
Thu, 20 Jun 2002 13:15:02 +0200
changeset 1048 75c7cc52082c
parent 1047 1cd99e473c08
child 1049 b44c11236369
permissions -rw-r--r--
*** empty log message ***

'From Smalltalk/X, Version:4.1.4 on 20-jun-2002 at 06:09:31 am'                 !

"{ Package: 'ca:Compress' }"

Object subclass:#ZipStream
        instanceVariableNames:'onStream hitEOF binary isReadOpen inputBytes outputBytes zstream'
        classVariableNames:'Z_FINISH Z_NO_FLUSH Z_SYNC_FLUSH Z_FULL_FLUSH 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'
!

!ZipStream primitiveDefinitions!
%{

/*
 * includes, defines, structure definitions
 * and typedefs come here.
 */

#include "compress/zlib.h"
#include "compress/zutil.h"

typedef enum {    e_infalteInit
                , e_infalteLoop
                , e_infalteEnd
} e_infalte;
                
typedef struct {
        z_stream        stream;
        Bytef *         in_ref;
        uLong           in_position;
        uLong           in_total;

        Bytef *         out_ref;
        uLong           out_position;
        uLong           out_total;
        uLong           out_limit;

        e_infalte       inflateMode;
        uLong           crc_32;
} zstream_s;

%}
! !


!ZipStream class methodsFor:'initialization'!

initialize
    |varZ_NO_FLUSH varZ_SYNC_FLUSH varZ_FULL_FLUSH varZ_FINISH varZ_DEFLATED
     varZ_DEFAULT_COMPRESSION varZ_BEST_COMPRESSION  varZ_DEF_MEM_LEVEL
     varZ_DEFAULT_STRATEGY varZ_FILTERED varZ_HUFFMAN_ONLY
     varHEAD_OS_CODE
    |
%{
    varZ_NO_FLUSH            = __MKSMALLINT( Z_NO_FLUSH );
    varZ_SYNC_FLUSH          = __MKSMALLINT( Z_SYNC_FLUSH );
    varZ_FULL_FLUSH          = __MKSMALLINT( Z_FULL_FLUSH );
    varZ_FINISH              = __MKSMALLINT( Z_FINISH );

    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_NO_FLUSH            := varZ_NO_FLUSH.
    Z_SYNC_FLUSH          := varZ_SYNC_FLUSH.
    Z_FULL_FLUSH          := varZ_FULL_FLUSH.
    Z_FINISH              := varZ_FINISH.

    Z_DEFLATED            := varZ_DEFLATED.

    Z_DEFAULT_COMPRESSION := varZ_DEFAULT_COMPRESSION.
    Z_DEFAULT_LEVEL       := 6.
    Z_BEST_COMPRESSION    := varZ_BEST_COMPRESSION.

    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_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 "
    HEAD_COMMENT          := 16r10.     " bit 4 set:  file comment present "
    HEAD_CRC              := 16r02.     " bit 1 set:  header CRC present "

    GZ_MAGIC_ID           := #[ 16r1f 16r8b ]

! !

!ZipStream class methodsFor:'instance creation'!

readOpenOn:aStream
    ^ self new readOpenOn:aStream
!

writeOpenOn:aStream
    ^ self writeOpenOn:aStream level:Z_DEFAULT_LEVEL
                            memLevel:Z_DEF_MEM_LEVEL
                            strategy:Z_DEFAULT_STRATEGY.
!

writeOpenOn:aStream level:level memLevel:memLevel strategy:strategy
    |z|

    z := self new.
    z writeOpenOn:aStream level:level memLevel:memLevel strategy:strategy.
  ^ z
! !

!ZipStream class methodsFor:'test'!

test
"
ZipStream test
"
   |fileContents compContents uncompContents in zip out|

   fileContents := 'smalltalk.rc' asFilename contentsOfEntireFile.

   in  := fileContents readStream.
   out := #[] writeStream.

   [ zip := self writeOpenOn:out.

     [in atEnd] whileFalse:[ |buf|
        buf := in nextAvailable:512.
        zip nextPutAll:buf.
     ].
   ] valueNowOrOnUnwindDo:[ zip ifNotNil:[ zip close ] ].

   compContents := out contents.
   in := compContents readStream.

   [ zip := self readOpenOn:in.
     uncompContents := zip contents.
   ] valueNowOrOnUnwindDo:[ zip ifNotNil:[ zip close ] ].

   fileContents = uncompContents ifFalse:[
        self halt:'contents differs'.
      ^ self
   ].
   Transcript showCR:'uncompressed size: ', fileContents size printString.
   Transcript showCR:'compressed   size: ', compContents size printString.

   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
        ]
        "/ zip nextPutAll:buf.
     ].
   ] 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
    self zerror:( self class name , ' not open' ).
!

invalidArgument
    self zerror:( 'invalid argument' ).
!

pastEnd
    self zerror:( 'end of stream' ).
!

zerror:anErrorOrNumber

    onStream := nil.

    self zclose.
    self error:( 'error: ', anErrorOrNumber printString ).
! !

!ZipStream methodsFor:'low level'!

zFlushInputBuffer
%{
    OBJ _zstreamObj = __INST( zstream );

    if( _zstreamObj != nil  )
    {
        zstream_s * _zstream;
        uInt        _inpos;
        Bytef     * _in_ref;

        _zstream  = (zstream_s *) __externalBytesAddress( _zstreamObj );
        _inpos    = _zstream->in_position;

        if( _inpos == 0 )
        {
            _zstream->stream.avail_in = 0;
            _zstream->stream.next_in  = Z_NULL;
            RETURN( self );
        }
        _in_ref = _zstream->in_ref;

        _zstream->stream.avail_in = _inpos;
        _zstream->stream.next_in  = _in_ref;
        _zstream->crc_32 = crc32( _zstream->crc_32, _in_ref, _inpos );
    }
%}.
    zstream ifNil:[ self errorNotOpen ].

    [
        self zflush:false.
        self zdeflate:Z_NO_FLUSH.
        self zinputAvailable

    ] whileTrue.
!

zFlushOutPutBuffer
    |errorNo|

    errorNo := nil.
%{
    OBJ _zstreamObj = __INST( zstream );

    if( _zstreamObj != nil  )
    {
        zstream_s * _zstream;
        int         _errorNo;

        _zstream = (zstream_s *) __externalBytesAddress( _zstreamObj );

        /* still data available */
        if( _zstream->out_position < _zstream->out_limit )
            RETURN( __MKSMALLINT (0) );

        _zstream->out_position = _zstream->out_limit = 0;

        if( _zstream->inflateMode != e_infalteLoop )
        {
            if( _zstream->inflateMode == e_infalteEnd )
            {
                __INST(hitEOF) = true;
                RETURN( __MKSMALLINT (0) );
            }

            if( _zstream->stream.avail_in == 0 )
                RETURN( __MKSMALLINT (0) );

            _zstream->inflateMode = e_infalteLoop;
        }
        _zstream->stream.avail_out = _zstream->out_total;
        _zstream->stream.next_out  = _zstream->out_ref;

        _errorNo = inflate( & _zstream->stream, Z_NO_FLUSH );

        if( _errorNo == Z_STREAM_END )
        {
            _errorNo = inflateEnd( & _zstream->stream );
            _zstream->inflateMode = e_infalteEnd;
        }
        if( _errorNo == Z_OK )
        {
            uInt _limit = _zstream->out_total - _zstream->stream.avail_out;

            _zstream->out_limit        = _limit;
            _zstream->stream.avail_out = 0;
            _zstream->stream.next_out  = Z_NULL;

            RETURN( __MKSMALLINT (_limit) );
        }
        errorNo = __MKSMALLINT( _errorNo );
    }
%}.
    zstream ifNil:[ self errorNotOpen ].
    self zerror:errorNo.
!

zNextAvailableBytes:count into:inBytes startingAt:start
%{
    OBJ _zstreamObj = __INST( zstream );

    if( (_zstreamObj != nil) && __bothSmallInteger(count, start) )
    {
        char *      _bytes;
        zstream_s * _zstream;
        int         _count, _offs, _capacity;
        uInt        _outpos;
        uInt        _limit;

        _zstream = (zstream_s *) __externalBytesAddress( _zstreamObj );

        _limit   = _zstream->out_limit;
        _outpos  = _zstream->out_position;
        _count   = __intVal( count );

        if( (_outpos >= _limit) || (_count <= 0) )
            RETURN( __MKSMALLINT (0) );

        if( (_offs = __intVal (start) - 1) < 0 )
            goto bad;

        if (__isBytes (inBytes)) {
            _bytes = __ByteArrayInstPtr(inBytes)->ba_element;
        } else if ( __isString(inBytes) ) {
            _bytes = __stringVal( inBytes );
        } else
            goto bad;

        _capacity = (int) _limit - _outpos;

        if(_count > _capacity )
            _count = _capacity;

        zmemcpy( (Bytef *) & _bytes[_offs], _zstream->out_ref + _outpos, _count );
        _zstream->out_position += _count;
        RETURN( __MKSMALLINT (_count) );
    }
bad:;
%}.
    zstream ifNil:[ self errorNotOpen ].
    self invalidArguments .
!

zNextByte
%{
    OBJ _zstreamObj = __INST( zstream );

    if( _zstreamObj != nil )
    {
        zstream_s * _zstream;
        uInt        _outPos;

        _zstream = (zstream_s *) __externalBytesAddress( _zstreamObj );
        _outPos  = _zstream->out_position;

        if( _outPos < _zstream->out_limit )
        {
            int _theByte = (Byte) _zstream->out_ref[ _outPos ];
            _zstream->out_position += 1;

            RETURN( __MKSMALLINT (_theByte) );
        }
        RETURN( nil );
    }    
%}.
    self errorNotOpen.
!

zNextPutByte:aByte
%{
    OBJ _zstreamObj = __INST( zstream );

    if( _zstreamObj != nil )
    {
        zstream_s * _zstream;
        uInt        _inpos;
        int         _theByte;

        _zstream  = (zstream_s *) __externalBytesAddress( _zstreamObj );
        _inpos    = _zstream->in_position;

        if( _inpos >= _zstream->in_total )
            RETURN( __MKSMALLINT (0) );

        _theByte = -1;

        if( __isCharacter(aByte) )
            _theByte = __intVal(__characterVal(aByte)) & 0xFF;
        else if( __isSmallInteger(aByte) )
        {
            _theByte = __intVal( aByte );

            if( (_theByte < 0) || (_theByte > 255) )
                goto bad;
        }
        else
            goto bad;
        
        _zstream->in_ref[_inpos] = (Byte) _theByte;
        _zstream->in_position   += 1;
        RETURN( __MKSMALLINT (1) );
    }
bad:;
%}.
    zstream ifNil:[ self errorNotOpen ].
    self invalidArguments.
!

zNextPutBytes:count from:inBytes startingAt:start
%{
    OBJ _zstreamObj = __INST( zstream );

    if( (_zstreamObj != nil) && __bothSmallInteger(count, start) )
    {
        int         _count, _offs, _bsize;
        char      * _bytes;
        zstream_s * _zstream;
        uInt        _inpos;
        uInt        _total;

        _zstream  = (zstream_s *) __externalBytesAddress( _zstreamObj );
        _inpos    = _zstream->in_position;
        _total    = _zstream->in_total;
        _count    = __intVal( count );

        if( (_inpos >= _total) || (_count <= 0) )
            RETURN( __MKSMALLINT (0) );

        if( (_offs = __intVal (start) - 1) < 0 )
            goto bad;

        if (__isBytes (inBytes)) {
            _bytes = __ByteArrayInstPtr(inBytes)->ba_element;
            _bsize = __byteArraySize( inBytes );
        }
        else if (__isString(inBytes)) {
            _bytes = __stringVal ( inBytes );
            _bsize = __stringSize( inBytes );
        } else
            goto bad;

        if( (_count + _offs) < _bsize )
        {
            int _capacity = (int) _total - _inpos;

            if(_count > _capacity )
                _count = _capacity;

            zmemcpy( _zstream->in_ref + _inpos, (Bytef *) & _bytes[_offs], _count );
            _zstream->in_position += _count;
            RETURN( __MKSMALLINT (_count) );
        }
    }
bad:;
%}.
    zstream ifNil:[ self errorNotOpen ].
    self invalidArguments.
!

zclose

    onStream := nil.
    hitEOF   := true.
    zstream ifNil:[^ self].

%{
    OBJ _zstreamObj = __INST( zstream );

    if( _zstreamObj != nil )
    {
        zstream_s * _zstream = (zstream_s *) __externalBytesAddress( _zstreamObj );

        __INST(zstream) = nil;

        if( _zstream->stream.state != NULL )
        {
            if( __INST(isReadOpen) == true )
                inflateEnd( & _zstream->stream );
            else
                deflateEnd( & _zstream->stream );
        }
        free( _zstream );
    }
%}.
    zstream := nil.
!

zdeflate:aLevel
    |errorNo|

    errorNo := nil.

%{
    OBJ _zstreamObj = __INST( zstream );

    if( (_zstreamObj != nil) && (__isSmallInteger(aLevel)) )
    {
        int _errorNo, _level;
        zstream_s * _zstream = (zstream_s *) __externalBytesAddress( _zstreamObj );

        _level   = __intVal( aLevel );
        _errorNo = deflate( & _zstream->stream, __intVal(aLevel) );

        if( _zstream->stream.avail_in == 0 )
        {
            _zstream->in_position    = 0;
            _zstream->stream.next_in = Z_NULL;
        }
        if( _errorNo == Z_STREAM_END ) RETURN( true  );
        if( _errorNo == Z_OK )         RETURN( false );

        errorNo = __MKSMALLINT( _errorNo );
    }
%}.
    errorNo ifNil:[
        zstream ifNil:[self errorNotOpen].
        self invalidArguments.
    ].
    self zerror:errorNo.
!

zdeflateEnd
    |errorNo|

    errorNo := nil.

%{
    OBJ _zstreamObj = __INST( zstream );

    if( _zstreamObj != nil )
    {
        int         _errorNo;
        zstream_s * _zstream = (zstream_s *) __externalBytesAddress( _zstreamObj );

        _errorNo = deflateEnd( & _zstream->stream );

        if( _errorNo == Z_OK )
            RETURN( self );

        errorNo = __MKSMALLINT( _errorNo );
    }
%}.
    errorNo ifNil:[ self errorNotOpen ].
    self zerror:errorNo.
!

zdeflateInit:aLevel memLevel:memLevel strategy:strategy
    |errorNo|

    errorNo := nil.

%{
    OBJ _zstreamObj = __INST( zstream );

    if(   (_zstreamObj != nil)
       && __isSmallInteger(aLevel)
       && __isSmallInteger(memLevel)
       && __isSmallInteger(strategy)
      )
    {
        int         _errorNo;
        zstream_s * _zstream = (zstream_s *) __externalBytesAddress( _zstreamObj );

        _errorNo = deflateInit2( & _zstream->stream
                               , __intVal( aLevel )
                               , Z_DEFLATED
                               , -MAX_WBITS
                               , __intVal( memLevel )
                               , __intVal( strategy )
                               );

        if( _errorNo == Z_OK )
            RETURN( self );

        errorNo = __MKSMALLINT( _errorNo );
    }
%}.
    errorNo ifNil:[
        zstream ifNil:[ self errorNotOpen ].
        self invalidArguments .
    ].
    self zerror:errorNo.
!

zflush:forced
    |len|

    len := 0.

%{
    OBJ _zstreamObj = __INST( zstream );

    if( _zstreamObj != nil )
    {
        uInt        _max, _len;
        zstream_s * _zstream = (zstream_s *) __externalBytesAddress( _zstreamObj );

        _max = _zstream->out_total;
        _len = _max - _zstream->stream.avail_out;

        if( (_len == 0) || ((forced == false) && (_len != _max)) )
            RETURN( __MKSMALLINT(0) );

        _zstream->stream.avail_out = _max;
        _zstream->stream.next_out  = _zstream->out_ref;

        len = __MKSMALLINT( _len );
    }
%}.
    zstream ifNil:[ self errorNotOpen ].
    self onStreamPutBytes:len from:outputBytes.
!

zgetCrc32

%{
    OBJ _zstreamObj = __INST( zstream );

    if( _zstreamObj != nil )
    {
        zstream_s * _zstream = (zstream_s *) __externalBytesAddress( _zstreamObj );
        RETURN ( __MKUINT(_zstream->crc_32) );
    }
%}.
    self errorNotOpen
!

zgetTotalIn
%{
    OBJ _zstreamObj = __INST( zstream );

    if( _zstreamObj != nil )
    {
        zstream_s * _zstream = (zstream_s *) __externalBytesAddress( _zstreamObj );
        RETURN ( __MKUINT(_zstream->stream.total_in) );
    }
%}.
    self errorNotOpen
!

zinflateInit
    |errorNo|

    errorNo := nil.

%{
    OBJ _zstreamObj = __INST( zstream );

    if( _zstreamObj != nil )
    {
        int         _errorNo;
        zstream_s * _zstream = (zstream_s *) __externalBytesAddress( _zstreamObj );

        _errorNo = inflateInit2( & _zstream->stream, -MAX_WBITS );

        if( _errorNo == Z_OK )
            RETURN( self );

        _zstream->stream.avail_in = 0;
        errorNo = __MKSMALLINT( _errorNo );
    }
%}.
    errorNo ifNil:[ self errorNotOpen ].
    self zerror:errorNo.
!

zinputAvailable
%{
    OBJ _zstreamObj = __INST( zstream );

    if( _zstreamObj != nil )
    {
        zstream_s * _zstream = (zstream_s *) __externalBytesAddress( _zstreamObj );

        if( _zstream->stream.avail_in != 0 )
            RETURN( true );

        RETURN( false );
    }
%}.
    self errorNotOpen
!

zinputPosition:count
%{
    OBJ _zstreamObj = __INST( zstream );

    if( (_zstreamObj != nil) && __isSmallInteger(count) )
    {
        int         _count;
        zstream_s * _zstream = (zstream_s *) __externalBytesAddress( _zstreamObj );

        _count = __intVal( count );

        if( _count < 0 )
        {
            _zstream->stream.next_in  = Z_NULL;
            _count = 0;
        }
        else
            _zstream->stream.next_in  = _zstream->in_ref;

        _zstream->stream.avail_in = _count;
        RETURN( __MKSMALLINT (_count) );
    }
%}.
    zstream ifNil:[ self errorNotOpen ].
    self invalidArguments .
!

zopen:aStream
    |outTotal inTotal|

    (onStream := aStream) ifNil:[ self pastEnd ].

    outputBytes := ExternalBytes unprotectedNew:8192.
    outTotal    := outputBytes size.

    inputBytes  := ExternalBytes unprotectedNew:8192.
    inTotal     := outputBytes size.
    binary      := false.
%{
    zstream_s * _zstream = (zstream_s *) malloc( sizeof(zstream_s) );

    if( _zstream )
    {
        OBJ     _zobj   = __MKEXTERNALADDRESS( _zstream );
        OBJ     _outObj = __INST( outputBytes );
        OBJ     _inpObj = __INST( inputBytes  );

        zmemzero( _zstream, sizeof(zstream_s) );

        _zstream->in_total         = __intVal( inTotal );
        _zstream->in_position      = 0;
        _zstream->in_ref           = (Bytef *) __externalBytesAddress( _inpObj );
        _zstream->stream.next_in   = Z_NULL;
        _zstream->stream.avail_in  = 0;
        _zstream->stream.total_in  = 0;

        _zstream->out_position     = 0;
        _zstream->out_limit        = 0;
        _zstream->out_total        = __intVal( outTotal );
        _zstream->out_ref          = (Bytef *) __externalBytesAddress( _outObj );
        _zstream->stream.next_out  = _zstream->out_ref;
        _zstream->stream.avail_out = _zstream->out_total;
        _zstream->stream.total_out = 0;

        _zstream->inflateMode      = e_infalteInit;

        _zstream->stream.zalloc    = (alloc_func)0;
        _zstream->stream.zfree     = (free_func) 0;
        _zstream->stream.opaque    = (voidpf)    0;

        _zstream->crc_32           = crc32( 0L, Z_NULL, 0 );

        __INST (zstream) = _zobj;
        __STORE(self, _zobj);
    }
%}.
    zstream ifNil:[ self zerror:'cannot allocate zbuffer' ].
    hitEOF := false.
! !

!ZipStream methodsFor:'private'!

onStreamPutBytes:count from:data

    onStream ifNil:[ self errorNotOpen ].
    onStream nextPutBytes:count from:data startingAt:1
!

onStreamPutLong:aLong
    |bytes value|

    bytes := ByteArray new:4.
    value := aLong.

    1 to:4 do:[:i|
        bytes at:i put:(value bitAnd:16rff).
        value := value bitShift:-8.
    ].
    self onStreamPutBytes:(bytes size) from:bytes
!

onStreamReadBytesInto:data

    onStream ifNil:[ self pastEnd ].
  ^ onStream nextBytes:(data size) into:data startingAt:1
! !

!ZipStream methodsFor:'private todo'!

readHeader
    |method flags|

    self isReadOpen ifFalse:[ self pastEnd ].

    "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

    self isWriteOpen ifFalse:[ self pastEnd ].

    "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
    ^ hitEOF ~~ false
!

isBinary
    "return true, if the stream is in binary (as opposed to text-) mode.
     The default when created is false.
    "
    ^ binary
!

isOpen
    ^ onStream notNil
!

isReadOpen
    ^ onStream notNil and:[isReadOpen == true]
!

isWriteOpen
    ^ onStream notNil and:[isReadOpen == false]
! !

!ZipStream methodsFor:'reading'!

contents
   |out buf bufSize count|

   self isReadOpen ifFalse:[self pastEnd].

   "use the maximum size read at time
   "
   bufSize := outputBytes size.

   binary ifFalse:[
        out := (String new:bufSize) writeStream.
        buf := String new:bufSize.
   ] ifTrue:[
        out := (ByteArray new:bufSize) writeStream.
        buf := ByteArray new:bufSize.
   ].

   [    count := self nextAvailableBytes:bufSize into:buf startingAt:1.
        count ~~ 0
   ] whileTrue:[
        out nextPutAll:buf startingAt:1 to:count
   ].
   ^ out contents

"
   |gzFile zip contents|

   gzFile := FileStream readonlyFileNamed:'/home/ca/C/Compress/zlib-1.1.4/Test/YYY.gz'.
   [
     zip := self new readOpenOn:gzFile.
     contents := zip contents.
   ] valueNowOrOnUnwindDo:[
        zip ifNotNil:[ zip close ].
        gzFile close.
   ].
   ^ contents
"

!

next
    |b|

    b := self nextByte.

    b ifNotNil:[
        binary ifTrue:[^ b ].
      ^ Character value:b
    ].
    ^ nil
!

next:count
    ^ self nextAvailable:count
!

nextAvailable:count
    |n buffer|

    self isReadOpen ifFalse:[ self pastEnd ].

    binary ifTrue:[
        buffer := ByteArray uninitializedNew:count
    ] ifFalse:[
        buffer := String new:count
    ].

    n := self nextAvailableBytes:count into:buffer startingAt:1.

    n == 0 ifTrue:[
        binary ifTrue:[
            ^ #[]
        ].
        ^ ''
    ].
    n ~~ count ifTrue:[ ^ buffer copyTo:n ].
  ^ buffer.
!

nextAvailableBytes:aCount into:inBytes startingAt:start
    |count offs|

    self isReadOpen ifFalse:[ self pastEnd ].
    self atEnd       ifTrue:[ ^ 0 ].

    count := aCount.
    offs  := start.

    [count > 0] whileTrue:[ |n|
        n := self zNextAvailableBytes:count into:inBytes startingAt:offs.

        n == 0 ifTrue:[
            n := self zFlushOutPutBuffer.

            n == 0 ifTrue:[
                self atEnd ifTrue:[ ^ offs - 1 ].

                n := self onStreamReadBytesInto:inputBytes.
                n == 0 ifTrue:[
                    self pastEnd
                ].
                self zinputPosition:n.
            ]
        ] ifFalse:[
            count := count - n.
            offs  := offs  + n.
        ]
    ].
    ^ aCount
!

nextByte
    |byte bytes|

    byte := self zNextByte.
    byte ifNotNil:[ ^ byte ].

    bytes := ByteArray new:1.

    (self nextAvailableBytes:1 into:bytes startingAt:1) == 1 ifTrue:[
        ^ bytes at:1
    ].
    "end of file detected
    "
    ^ nil
! !

!ZipStream methodsFor:'startup & release'!

close
    zstream ifNil:[^ self].

    self isWriteOpen ifTrue:[
        self zFlushInputBuffer.

        [   self zflush:true.
            self zdeflate:Z_FINISH
        ] whileFalse.

        self zflush:true.
        self zdeflateEnd.

        self onStreamPutLong:(self zgetCrc32  ).    " write crc "
        self onStreamPutLong:(self zgetTotalIn).    " write total size "
    ].
    self zclose.
!

readOpenOn:aStream

    isReadOpen := true.

    self zopen:aStream.
    self zinflateInit.
    self readHeader.
!

writeOpenOn:aStream level:level memLevel:memLevel strategy:strategy

    isReadOpen := false.

    self zopen:aStream.
    self zdeflateInit:level memLevel:memLevel strategy:strategy.
    self writeHeader.
! !

!ZipStream methodsFor:'writing'!

flush
    "flush output buffer
    "
    self flush:true
!

flush:forced

    self isWriteOpen ifTrue:[
        self zflush:forced
    ] ifFalse:[
        onStream ifNil:[self pastEnd]
    ].
!

nextPut:aCharacter

    self isWriteOpen ifFalse:[ self pastEnd ].

    [ (self zNextPutByte:aCharacter) == 0 ] whileTrue:[
        self zFlushInputBuffer
    ].
!

nextPutAll:buffer
    self nextPutBytes:(buffer size) from:buffer startingAt:1
!

nextPutAll:aCollection startingAt:start to:stop
    self nextPutBytes:(stop - start + 1) from:aCollection startingAt:start
!

nextPutByte:aByte
    self nextPut:aByte.
!

nextPutBytes:aCount from:inBytes startingAt:start
    |count offs|

    self isWriteOpen ifFalse:[ self pastEnd ].

    count := aCount.
    offs  := start.

    [count > 0] whileTrue:[ |n|
        n := self zNextPutBytes:count from:inBytes startingAt:offs.

        n == 0 ifTrue:[
            self zFlushInputBuffer
        ] ifFalse:[
            count := count - n.
            offs  := offs  + n.
        ]
    ].
    ^ aCount
! !

!ZipStream class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic2/ZipStream.st,v 1.5 2002-06-20 11:15:02 ca Exp $'
! !
ZipStream initialize!