ZipStream.st
author Claus Gittinger <cg@exept.de>
Fri, 29 Aug 2003 21:31:33 +0200
changeset 1308 d7bea6d0b3b6
parent 1197 c86e858c2893
child 1439 134b4620d6d0
permissions -rw-r--r--
*** empty log message ***

"
 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:libbasic2' }"

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:'System-Compress'
!

!ZipStream primitiveDefinitions!
%{

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

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

typedef enum {
	  e_opmode_unspecified          /* processing done */
	, e_opmode_deflate              /* running deflate */
	, e_opmode_inflate              /* running inflate */
} e_opmode;

typedef struct {
	z_stream        stream;         /* pointer to the external in -stream */
	Bytef *         in_ref;         /* size    of the external in -stream */
	Bytef *         out_ref;        /* pointer to the external out-stream */
	uLong           out_total;      /* size    of the external out-stream */

	e_opmode        op_mode;        /* current operational mode */
	uLong           crc_32;         /* keeps the current crc */

	Bytef           tail_buff[ 8 ]; /* store the tail in the read modus */
	uLong           tail_size;      /* to check the crc and data length */
} zstream_s;

%}
! !

!ZipStream 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
"
    Zip compression and decompression (used in gzip and zip)

    [author:]
        Claus Atzkern

    [instance variables:]

    [class variables:]

    [see also:]

"
!

examples
"

                                                                [exBegin]
    |compressed zipStream|

    compressed := #[] writeStream.
    zipStream := self writeOpenOn:compressed.
    zipStream nextPutAll:'This is some text 1234567890'.
    zipStream flush.
    self information:compressed contents size printString.

self halt.
    zipStream := self readOpenOn:compressed contents readStream.
    self information:zipStream contents.
                                                                [exEnd]
"
! !

!ZipStream class methodsFor:'initialization'!

initialize
    "setup class attributes derived from the library
    "
    |z_deflated os_code|
%{
    z_deflated = __MKSMALLINT( Z_DEFLATED );
    os_code    = __MKSMALLINT( OS_CODE );
%}.

    Z_DEFLATED            := z_deflated.

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

    GZ_MAGIC_ID           := #[ 16r1f 16r8b ]

! !

!ZipStream methodsFor:'low level'!

zclose
    "low level close of the zip stream
    "
%{
    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 )
		inflateEnd( & _zstream->stream );
	    else
		deflateEnd( & _zstream->stream );
	}
	free( _zstream );
    }
%}.
!

zdeflate
    "low level - deflate
    "
    |errorNo|

    errorNo := nil.

%{
    OBJ _zstreamObj = __INST( zstream );

    if( _zstreamObj != nil )
    {
	int         _errorNo, _action;
	uLong       _bfsize;
	zstream_s * _zstream = (zstream_s *) __externalBytesAddress( _zstreamObj );

	if( _zstream->op_mode != e_opmode_deflate )
	    RETURN( false );

	_bfsize = _zstream->out_total;

	if( _zstream->stream.state == NULL )
	{
	    /* processing finished; write crc_32 and the total size
	    */
	    uLong   v, i;
	    Bytef * p = _zstream->out_ref;

	    v = _zstream->crc_32;
	    for( i = 0; i < 4; ++i ) { p[i] = v & 0xff; v >>= 8; }

	    v = _zstream->stream.total_in;
	    for( i = 4; i < 8; ++i ) { p[i] = v & 0xff; v >>= 8; }

	    _zstream->op_mode          = e_opmode_unspecified;
	    _zstream->stream.avail_in  = 0;
	    _zstream->stream.next_in   = Z_NULL;
	    _zstream->stream.avail_out = _bfsize - 8;
	    RETURN( true );
	}
	_zstream->stream.avail_out = _bfsize;
	_zstream->stream.next_out  = _zstream->out_ref;

	_action  = (__INST(hitEOF) == true) ? Z_FINISH : Z_NO_FLUSH;        
	_errorNo = deflate( & _zstream->stream, _action );

	if( _errorNo == Z_STREAM_END )
	{
	    _zstream->stream.avail_in = 0;
	    _zstream->stream.next_in  = Z_NULL;
	    _errorNo = deflateEnd( & _zstream->stream );
	}

	if( _errorNo == Z_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 - deflateInit
    "
    |errorNo level|

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

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

	_zstream->op_mode = e_opmode_deflate;

	_errorNo = deflateInit2( & _zstream->stream
			       , __intVal( level )
			       , Z_DEFLATED
			       , -MAX_WBITS
			       , DEF_MEM_LEVEL
			       , Z_DEFAULT_STRATEGY
			       );

	if( _errorNo == Z_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 )
    {
	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
    "
    |errorNo tailError|

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

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

	_zstream = (zstream_s *) __externalBytesAddress( _zstreamObj );

	if( _zstream->op_mode != e_opmode_inflate )
	    RETURN( nil );

	_avail_in = _zstream->stream.avail_in;

	if( _zstream->stream.state == NULL )
	{
	    /* processing finished : check crc and data length */
	    Bytef * _next_in;
	    Bytef * _buff;
	    uLong   _tnum;
	    int     _i;

	    _next_in   = _zstream->stream.next_in;
	    _buff = _zstream->tail_buff;
	    _tnum = _zstream->tail_size;

	    while( (_avail_in > 0) && (_tnum < 8) )
	    {
	       _buff[_tnum] = * _next_in;

		++_next_in;
		++_tnum;
		--_avail_in;
	    }
	    _zstream->tail_size = _tnum;

	    if( _tnum < 8 )                     /* test whether tail is read */
		RETURN( __MKSMALLINT (0) );     /* need more data */

	    /* compute and check crc */
	    for( _tnum = 0, _i = 4; --_i >= 0; _tnum = (_tnum << 8) + _buff[_i] );

	    if( _tnum != _zstream->crc_32 )
		{ tailError = __MKSMALLINT( 1 ); goto badTail; }

	    /* compute and check data length */
	    for( _tnum = 0, _i = 8; --_i >= 4; _tnum = (_tnum << 8) + _buff[_i] );

	    if( _zstream->stream.total_out != _tnum )
		{ tailError = __MKSMALLINT( 2 ); goto badTail; }

	    _zstream->op_mode = e_opmode_unspecified;
	    RETURN( nil );
	}
	if( _avail_in == 0 )
	    RETURN( __MKSMALLINT (0) );

	_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 );

	if( _errorNo == Z_OK )
	{
	    _count = _zstream->out_total - _zstream->stream.avail_out;

	    if( _count > 0 )
		_zstream->crc_32 = crc32( _zstream->crc_32, _zstream->out_ref, _count );

	    RETURN( __MKSMALLINT (_count) );
	}
	errorNo = __MKSMALLINT( _errorNo );
    }
badTail:;
%}.
    errorNo ifNil:[
	tailError ifNotNil:[
	    tailError == 1 ifTrue:[
		self zerror:'invalid compressed data--crc error'
	    ].
	    self zerror:'invalid compressed data--length error'
	].
	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 = 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.
!

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  );

	zmemzero( _zstream, sizeof(zstream_s) );

	_zstream->in_ref           = (Bytef *) __externalBytesAddress( _inpObj );
	_zstream->stream.next_in   = Z_NULL;
	_zstream->stream.avail_in  = 0;
	_zstream->stream.total_in  = 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->stream.zalloc    = (alloc_func)0;
	_zstream->stream.zfree     = (free_func) 0;
	_zstream->stream.opaque    = (voidpf)    0;

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

	__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 )
	{
	    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.
! !

!ZipStream methodsFor:'startup & release'!

openWithMode:aMode on:aStream

    super openWithMode:aMode on:aStream.
    self isReadable ifTrue:[
        "Check for the gzip magic id"
        |flags|

        GZ_MAGIC_ID do:[:b|
            onStream nextByte ~~ b ifTrue:[ self zerror:'version error' ]
        ].

        onStream nextByte ~~ 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"
            [ (b := onStream nextByte) ~~ 0 ] whileTrue.
        ].

        (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 ].

        "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 class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic2/ZipStream.st,v 1.21 2003-08-29 19:31:33 cg Exp $'
! !

ZipStream initialize!