CompressionStream.st
author Claus Gittinger <cg@exept.de>
Fri, 31 Jul 2009 14:15:06 +0200
changeset 2192 aa40ad91e77a
parent 2191 7cb40c5e5511
child 2194 38a073a3261b
permissions -rw-r--r--
fixes

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

Stream subclass:#CompressionStream
	instanceVariableNames:'onStream hitEOF binary position readLimit mode inputBytes
		outputBytes zstream'
	classVariableNames:'BlockSize'
	poolDictionaries:''
	category:'System-Compress'
!

!CompressionStream 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
"
    Abstract superclass of streams that compress or deconpress data

    [author:]
	Claus Atzkern

    [instance variables:]

    [class variables:]

    [see also:]

"
! !

!CompressionStream class methodsFor:'initialization'!

initialize
    BlockSize := 6.
! !

!CompressionStream class methodsFor:'instance creation'!

readOpenOn:aStream
    "open to read data from an compressed stream"

    ^ self basicNew openWithMode:#readonly on:aStream
!

writeOpenOn:aStream
    "open to write data compressed to stream"

    ^ self basicNew openWithMode:#writeonly on:aStream
! !

!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'.
!

pastEndRead
    self zerror:'end of stream'.
    ^ nil

    "Modified: / 18-11-2006 / 15:37:08 / cg"
!

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
	].
    ].
    StreamError 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'!

z_nextAvailableInto:aCollection startingAt:offset
    ^ self z_nextAvailableInto:aCollection startingAt:offset maxCount:nil
!

z_nextAvailableInto:aCollection startingAt:offset maxCount:maxCount
    "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 ifTrue:[
        self zerror:'invalid arguments'
    ].
    count == 0 ifTrue:[
        ^ 0
    ].

    count := avail min:count.
    maxCount notNil ifTrue:[ count := count min:maxCount ].

    start := position.
    position := position + count.

%{  
    unsigned char * _dstPt;
    int             _count = __intVal( count );
    int             _offset = __intVal( offset );
    unsigned char * _srcPt;
    OBJ             _srcObj = __INST( outputBytes );

    if( __isBytes(aCollection) ) {
        _dstPt = (unsigned char *) (__byteArrayVal(aCollection));
    } else if (__isString(aCollection)) {
        _dstPt = (unsigned char *) (__stringVal( aCollection));
    } else {
        goto error;
    }

    _dstPt  = _dstPt + _offset - 1;

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

    memcpy(_dstPt, _srcPt, _count);

    RETURN(__MKSMALLINT(_count));

error: ;
%}.

    ^ self zerror:'invalid argument'
!

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
!

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

contentsSpecies
    "return the kind of object to be returned by sub-collection builders"

    binary == true ifTrue:[^ ByteArray].
    ^ String
!

onStreamPutBytes:count from:data
    "write compressed data to the (output) stream"

    onStream nextPutBytes:count from:data startingAt:1
! !

!CompressionStream methodsFor:'queries'!

atEnd
    "return true if the end of the compressed input stream has been reached"

    ^ self canReadWithoutBlocking not
!

canReadWithoutBlocking
    "returns true if data is available for reading;
     false if the stream is at end.
     Updates the readLimit and position"

    |n|

    mode == #readonly ifFalse:[
        self errorWriteOnly
    ].
    hitEOF == true ifTrue:[^ false].

    position >= readLimit ifTrue:[
        [(readLimit := self zinflate) == 0] whileTrue:[
            n := onStream nextBytes:(inputBytes size) into:inputBytes startingAt:1.

            n == 0 ifTrue:[
                hitEOF := true.
                ^ false
            ].
            self zset_avail_in:n.
        ].
        readLimit isNil ifTrue:[
            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
!

isReadable
    "return true, if this stream can be read from"

    ^ mode == #readonly
!

isWritable
    "return true, if this stream can be written to"

    ^ mode == #writeonly
! !

!CompressionStream methodsFor:'reading'!

contents
    "return the entire contents of and close the stream"

    |species stream bfsize buffer count|

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

    species := self contentsSpecies.
    buffer  := species new:bfsize.
    stream  := WriteStream on:(species new:bfsize).

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

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

next
    "return the next element, a character or byte (textmode)
     return nil, if there are no more elements"

    |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
!

next:n
    "return the next count elements of the stream as a collection.
     Redefined to return a String or ByteArray and for optimization"

    |data count offset species|

    species := self contentsSpecies.

    self canReadWithoutBlocking ifFalse:[
	^ species new
    ].
    data := species new:n.
    offset := 1.

    [self canReadWithoutBlocking] whileTrue:[
	count  := self z_nextAvailableInto:data startingAt:offset.
	offset := count + offset.
	offset > n ifTrue:[^ data]
    ].
    ^ data copyFrom:1 to:(offset - 1)
!

next:n into:aBuffer startingAt:startIndex
    "read the next n elements of the stream into aBuffer.
     Return the number of bytes read."

    |count remaining offset|

    self canReadWithoutBlocking ifFalse:[
        ^ 0
    ].
    offset := startIndex.
    remaining := n.

    [self canReadWithoutBlocking] whileTrue:[
        count  := self z_nextAvailableInto:aBuffer startingAt:offset maxCount:remaining.
        offset := count + offset.
        remaining := remaining - count.
        remaining == 0 ifTrue:[^ n]
    ].
    ^ n - remaining
!

skip:count
    "skip count objects, return the receiver
     redefined for optimization"

    |n avail|

    n := count.

    n <= 0 ifTrue:[
	n ~~ 0 ifTrue:[
	    "dont know how to unread ..."
	    PositionError raiseRequest
	].
	^ self
    ].

    [self canReadWithoutBlocking] whileTrue:[
	avail := readLimit - position.

	avail >= n ifTrue:[
	    position := position + n.
	    ^ self
	].
	position := readLimit := 0. "/ reset input
	n := n - avail.
    ].
! !

!CompressionStream methodsFor:'startup & release'!

close
    "close the zip-stream"

    hitEOF := true.
    zstream notNil ifTrue:[
	self flush.
	self closeZStream.
    ].
!

openWithMode:aMode on:aStream
    "open the zip-stream on a stream
     can be reimplemented to do some additional stuff (e.g. gzip header) like
     in the ZipStream
    "
    ^ self streamOpenWithMode:aMode on:aStream.
!

streamOpenWithMode:aMode on:aStream
    "open the compression 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
    "

    aStream isNil ifTrue:[
	^ self errorNotOpen
    ].

    onStream    := aStream.
    mode        := aMode.
    outputBytes := ExternalBytes unprotectedNew:16384.
    inputBytes  := ExternalBytes unprotectedNew:16384.
    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 and close the stream"

    contents do:[:c| self nextPut:c].
    self close.
!

flush
    "flush the input and output buffer"

    |continue availOut|

    self isWritable ifFalse:[^ self].
    self zset_avail_in:position.

    position := 0.

    [   continue := self zdeflate.
	availOut := self zget_avail_out.

	availOut > 0 ifTrue:[
	    self onStreamPutBytes:availOut from:outputBytes
	].

    ] doWhile:[ continue == true ].
!

nextPut:aByteOrCharacter
    "write the argument, aByteOrCharacter"

    position == inputBytes size ifTrue:[self flush].
    position := position + 1.
    inputBytes at:position put:aByteOrCharacter asInteger.
!

nextPutAll:aCollection
    |limit|

    limit := inputBytes size.

    aCollection do:[:aByteOrCharacter|
	position == limit ifTrue:[self flush].
	position := position + 1.
	inputBytes at:position put:aByteOrCharacter asInteger.
    ].
    ^ aCollection
! !

!CompressionStream class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic2/CompressionStream.st,v 1.25 2009-07-31 12:15:06 cg Exp $'
! !

CompressionStream initialize!