CompressionStream.st
author ca
Thu, 22 Aug 2002 09:25:12 +0200
changeset 1079 b6e148cf5df4
parent 1062 211b3cb6d628
child 1080 fe4e074affae
permissions -rw-r--r--
*** empty log message ***

"{ 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 closeZStream.
    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
    "the compressin-stream was garbage collected;
     close the underlying zip-stream
    "
    self closeZStream.
!

finalizeCopy:aZStream
    "used for finalization to close the underlying zip-stream
    "
    zstream := aZStream.
! !

!CompressionStream methodsFor:'low level'!

zclose
    "low level close of the zip stream
    "
    ^ self subclassResponsibility
!

zdeflate
    "low level - deflate
     returns false if the deflate operation is finished otherwise true.
    "
    ^ self subclassResponsibility
!

zdeflateInit
    "low level - deflateInit
     initialize the deflate mode, write header ...
    "
    ^ self subclassResponsibility
!

zget_avail_out
    "low level - get the number of available out bytes
    "
    ^ self subclassResponsibility
!

zinflate
    "low level - inflate
     returns nil if at uncompress is finished, or the number of
     available bytes in the output-buffer.
    "
    ^ self subclassResponsibility
!

zinflateInit
    "low level - inflateInit
     initialize the inflate mode, read and check header ...
    "
    ^ self subclassResponsibility
!

z_nextAvailableInto:aCollection startingAt:offset
    "read the next available bytes into a collection, a string or byteArray;
     returns the size read
    "
    |start count avail|

    avail := readLimit - position.
    avail > 0 ifFalse:[^ 0].

    count := aCollection size - offset + 1.

    count > 0 ifFalse:[
        count < 0 ifTrue:[
            self zerror:'invalid arguments'
        ].
        ^ 0
    ].
    count    := avail min:count.
    start    := position.
    position := position + count.

%{  unsigned char * _dstPt;

    if( __isBytes(aCollection) ) {
        _dstPt = (unsigned char *) (__ByteArrayInstPtr(aCollection)->ba_element);
    } else if (__isString(aCollection)) {
        _dstPt = (unsigned char *) (__stringVal( aCollection));
    } else
        _dstPt = (unsigned char *) 0;

    if( _dstPt )
    {
        int             _loop, _count, _offset;
        unsigned char * _srcPt;
        OBJ             _srcObj = __INST( outputBytes );

        _offset = __intVal( offset );
        _dstPt  = _dstPt + _offset - 1;

        _srcPt  = (unsigned char *) __externalBytesAddress( _srcObj );
        _srcPt += __intVal( start );
        _count  = __intVal( count );

        for( _loop = 0; _loop < _count; ++_loop )
            * _dstPt++ = * _srcPt++;

        RETURN(__MKSMALLINT(_count));
    }
%}.

    ^ self zerror:'invalid argument'
!

zopen
    "low level - opens the zip stream
     create the resources ...
    "
    ^ self subclassResponsibility
!

zset_avail_in:count
    "set the 'avail_in' and compute the crc
    "
    ^ self subclassResponsibility
! !

!CompressionStream methodsFor:'private'!

closeZStream
    "close the zip-stream
    "
    onStream := mode := nil.
    hitEOF   := true.

    zstream ifNotNil:[
        self unregisterForFinalization.
        self zclose.
        zstream := nil.
    ].
!

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
!

canReadWithoutBlocking
    "returns true if data are available for reading;
     false if the stream is at end.
     updates the readLimit and position
    "
    mode == #readonly ifFalse:[
        self errorReadOnly
    ].
    hitEOF == true ifTrue:[ ^ false ].

    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.
          ^ false
        ].
        position := 0.
    ].
    ^ true
!

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;
     after reading the stream is closed.
    "
    |stream bfsize buffer count|

    mode == #readonly ifFalse:[ self errorReadOnly ].
    bfsize := outputBytes size.

    binary ifTrue:[
        stream := ByteArray new:bfsize.
        buffer := ByteArray new:bfsize.
    ] ifFalse:[
        stream := String new:bfsize.
        buffer := String new:bfsize.
    ].
    stream := stream writeStream.

    [ self canReadWithoutBlocking ] whileTrue:[
        count := self z_nextAvailableInto:buffer startingAt:1.

        count == bfsize ifTrue:[
            stream nextPutAll:buffer.
        ] ifFalse:[
            count > 0 ifTrue:[    
                stream nextPutAll:(buffer copyFrom:1 to:count)
            ]
        ].
    ].
    self close.
  ^ stream contents
!

next
    "return the next element, a character or byte (textmode)
     if there is  more element, nil is returned
    "
    |byte|

    self canReadWithoutBlocking ifFalse:[
        "there is no more element; the stream is at end"
        ^ nil
    ].
    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 closeZStream.
    ].
!

openWithMode:aMode on:aStream
    "open the zip-stream on a stream
         #readonly    uncompress the data derived from the read-stream,  aStream
         #writeonly   compress   the data and write to the write-stream, 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'!

contents:contents
    "write the entire contents to the stream;
     after writing the stream is closed.
    "
    contents do:[:c| self nextPut:c ].
    self close.
!

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 ~~ #writeonly ifTrue:[
            zstream ifNil:[self errorNotOpen].
            self errorWriteOnly.
        ].
        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!