CompressionStream.st
changeset 2190 6c3f9241753a
parent 2005 a6ef1083aa32
child 2191 7cb40c5e5511
equal deleted inserted replaced
2189:42a2a9549bea 2190:6c3f9241753a
     1 "
     1 "
     2  COPYRIGHT (c) 2002 by eXept Software AG
     2  COPYRIGHT (c) 2002 by eXept Software AG
     3               All Rights Reserved
     3 	      All Rights Reserved
     4 
     4 
     5  This software is furnished under a license and may be used
     5  This software is furnished under a license and may be used
     6  only in accordance with the terms of that license and with the
     6  only in accordance with the terms of that license and with the
     7  inclusion of the above copyright notice.   This software may not
     7  inclusion of the above copyright notice.   This software may not
     8  be provided or otherwise made available to, or used by, any
     8  be provided or otherwise made available to, or used by, any
    22 !CompressionStream class methodsFor:'documentation'!
    22 !CompressionStream class methodsFor:'documentation'!
    23 
    23 
    24 copyright
    24 copyright
    25 "
    25 "
    26  COPYRIGHT (c) 2002 by eXept Software AG
    26  COPYRIGHT (c) 2002 by eXept Software AG
    27               All Rights Reserved
    27 	      All Rights Reserved
    28 
    28 
    29  This software is furnished under a license and may be used
    29  This software is furnished under a license and may be used
    30  only in accordance with the terms of that license and with the
    30  only in accordance with the terms of that license and with the
    31  inclusion of the above copyright notice.   This software may not
    31  inclusion of the above copyright notice.   This software may not
    32  be provided or otherwise made available to, or used by, any
    32  be provided or otherwise made available to, or used by, any
    38 documentation
    38 documentation
    39 "
    39 "
    40     Abstract superclass of streams that compress or deconpress data
    40     Abstract superclass of streams that compress or deconpress data
    41 
    41 
    42     [author:]
    42     [author:]
    43         Claus Atzkern
    43 	Claus Atzkern
    44 
    44 
    45     [instance variables:]
    45     [instance variables:]
    46 
    46 
    47     [class variables:]
    47     [class variables:]
    48 
    48 
   120 
   120 
   121 zerror:anError
   121 zerror:anError
   122     |error|
   122     |error|
   123 
   123 
   124     zstream isNil ifTrue:[
   124     zstream isNil ifTrue:[
   125         error := 'not open'.
   125 	error := 'not open'.
   126     ] ifFalse:[
   126     ] ifFalse:[
   127         anError isNumber ifTrue:[
   127 	anError isNumber ifTrue:[
   128                      anError ==  1 ifTrue:[ error := 'stream at end' ]
   128 		     anError ==  1 ifTrue:[ error := 'stream at end' ]
   129             ifFalse:[anError == -1 ifTrue:[ error := 'processing error: ', anError printString ]
   129 	    ifFalse:[anError == -1 ifTrue:[ error := 'processing error: ', anError printString ]
   130             ifFalse:[anError == -2 ifTrue:[ error := 'processing error' ]
   130 	    ifFalse:[anError == -2 ifTrue:[ error := 'processing error' ]
   131             ifFalse:[anError == -3 ifTrue:[ error := 'input data are corrupted' ]
   131 	    ifFalse:[anError == -3 ifTrue:[ error := 'input data are corrupted' ]
   132             ifFalse:[anError == -4 ifTrue:[ error := 'not enough memory' ]
   132 	    ifFalse:[anError == -4 ifTrue:[ error := 'not enough memory' ]
   133             ifFalse:[anError == -5 ifTrue:[ error := 'not enough memory in the output stream' ]
   133 	    ifFalse:[anError == -5 ifTrue:[ error := 'not enough memory in the output stream' ]
   134             ifFalse:[anError == -6 ifTrue:[ error := 'version error' ]
   134 	    ifFalse:[anError == -6 ifTrue:[ error := 'version error' ]
   135             ifFalse:[
   135 	    ifFalse:[
   136                     error := 'compressing error: ', anError printString                
   136 		    error := 'compressing error: ', anError printString
   137             ]]]]]]].
   137 	    ]]]]]]].
   138         ] ifFalse:[
   138 	] ifFalse:[
   139             error := anError printString
   139 	    error := anError printString
   140         ].
   140 	].
   141     ].
   141     ].
   142     StreamError raiseErrorString:(self class name , ': ', error).
   142     StreamError raiseErrorString:(self class name , ': ', error).
   143 ! !
   143 ! !
   144 
   144 
   145 !CompressionStream methodsFor:'finalization'!
   145 !CompressionStream methodsFor:'finalization'!
   146 
   146 
   147 executor
   147 executor
   148     "redefined to return a lightweight copy 
   148     "redefined to return a lightweight copy
   149      - all we need is the memory handle"
   149      - all we need is the memory handle"
   150 
   150 
   151     ^ self class basicNew finalizeCopy:zstream.    
   151     ^ self class basicNew finalizeCopy:zstream.
   152 !
   152 !
   153 
   153 
   154 finalize
   154 finalize
   155     "the compressin-stream was garbage collected;
   155     "the compressin-stream was garbage collected;
   156      close the underlying zip-stream"
   156      close the underlying zip-stream"
   164     zstream := aZStream.
   164     zstream := aZStream.
   165 ! !
   165 ! !
   166 
   166 
   167 !CompressionStream methodsFor:'low level'!
   167 !CompressionStream methodsFor:'low level'!
   168 
   168 
   169 z_nextAvailableInto:aCollection startingAt:offset
   169 z_nextAvailableInto:aCollection startingAt:offset maxCount:maxCount
   170     "read the next available bytes into a collection, a string or byteArray;
   170     "read the next available bytes into a collection, a string or byteArray;
   171      returns the size read"
   171      returns the size read"
   172 
   172 
   173     |start count avail|
   173     |start count avail|
   174 
   174 
   175     avail := readLimit - position.
   175     avail := readLimit - position.
   176     avail > 0 ifFalse:[^ 0].
   176     avail > 0 ifFalse:[^ 0].
   177 
   177 
   178     count := aCollection size - offset + 1.
   178     count := aCollection size - offset + 1.
   179 
   179 
   180     count > 0 ifFalse:[
   180     count < 0 ifTrue:[
   181 	count < 0 ifTrue:[
   181 	self zerror:'invalid arguments'
   182 	    self zerror:'invalid arguments'
   182     ].
   183 	].
   183     count == 0 ifTrue:[
   184 	^ 0
   184 	^ 0
   185     ].
   185     ].
   186     count    := avail min:count.
   186 
   187     start    := position.
   187     count := avail min:count.
       
   188     maxCount notNil ifTrue:[ count := count min:maxCount ].
       
   189 
       
   190     start := position.
   188     position := position + count.
   191     position := position + count.
   189 
   192 
   190 %{  unsigned char * _dstPt;
   193 %{  unsigned char * _dstPt;
   191 
   194 
   192     if( __isBytes(aCollection) ) {
   195     if( __isBytes(aCollection) ) {
   217 %}.
   220 %}.
   218 
   221 
   219     ^ self zerror:'invalid argument'
   222     ^ self zerror:'invalid argument'
   220 !
   223 !
   221 
   224 
       
   225 z_nextAvailableInto:aCollection startingAt:offset
       
   226     ^ self z_nextAvailableInto:aCollection startingAt:offset maxCount:nil
       
   227 !
       
   228 
   222 zclose
   229 zclose
   223     "low level close of the zip stream"
   230     "low level close of the zip stream"
   224 
   231 
   225     ^ self subclassResponsibility
   232     ^ self subclassResponsibility
   226 !
   233 !
   315      updates the readLimit and position"
   322      updates the readLimit and position"
   316 
   323 
   317     |n|
   324     |n|
   318 
   325 
   319     mode == #readonly ifFalse:[
   326     mode == #readonly ifFalse:[
   320         self errorWriteOnly
   327 	self errorWriteOnly
   321     ].
   328     ].
   322     hitEOF == true ifTrue:[^ false].
   329     hitEOF == true ifTrue:[^ false].
   323 
   330 
   324     position >= readLimit ifTrue:[
   331     position >= readLimit ifTrue:[
   325         [(readLimit := self zinflate) == 0] whileTrue:[ 
   332 	[(readLimit := self zinflate) == 0] whileTrue:[
   326             n := onStream nextBytes:(inputBytes size) into:inputBytes startingAt:1.
   333 	    n := onStream nextBytes:(inputBytes size) into:inputBytes startingAt:1.
   327 
   334 
   328             n == 0 ifTrue:[
   335 	    n == 0 ifTrue:[
   329                 hitEOF := true.
   336 		hitEOF := true.
   330                 ^ false
   337 		^ false
   331             ].
   338 	    ].
   332             self zset_avail_in:n.
   339 	    self zset_avail_in:n.
   333         ].
   340 	].
   334         readLimit isNil ifTrue:[
   341 	readLimit isNil ifTrue:[
   335             hitEOF := true.
   342 	    hitEOF := true.
   336             ^ false
   343 	    ^ false
   337         ].
   344 	].
   338         position := 0.
   345 	position := 0.
   339     ].
   346     ].
   340     ^ true
   347     ^ true
   341 !
   348 !
   342 
   349 
   343 isBinary
   350 isBinary
   371     "return the entire contents of and close the stream"
   378     "return the entire contents of and close the stream"
   372 
   379 
   373     |species stream bfsize buffer count|
   380     |species stream bfsize buffer count|
   374 
   381 
   375     mode == #readonly ifFalse:[
   382     mode == #readonly ifFalse:[
   376         self errorWriteOnly
   383 	self errorWriteOnly
   377     ].
   384     ].
   378     bfsize := outputBytes size.
   385     bfsize := outputBytes size.
   379 
   386 
   380     species := self contentsSpecies.
   387     species := self contentsSpecies.
   381     buffer  := species new:bfsize.
   388     buffer  := species new:bfsize.
   382     stream  := WriteStream on:(species new:bfsize).
   389     stream  := WriteStream on:(species new:bfsize).
   383 
   390 
   384     [self canReadWithoutBlocking] whileTrue:[
   391     [self canReadWithoutBlocking] whileTrue:[
   385         count := self z_nextAvailableInto:buffer startingAt:1.
   392 	count := self z_nextAvailableInto:buffer startingAt:1.
   386 
   393 
   387         count == bfsize ifTrue:[
   394 	count == bfsize ifTrue:[
   388             stream nextPutAll:buffer.
   395 	    stream nextPutAll:buffer.
   389         ] ifFalse:[
   396 	] ifFalse:[
   390             count > 0 ifTrue:[    
   397 	    count > 0 ifTrue:[
   391                 stream nextPutAll:buffer startingAt:1 to:count.
   398 		stream nextPutAll:buffer startingAt:1 to:count.
   392             ]
   399 	    ]
   393         ].
   400 	].
   394     ].
   401     ].
   395     self close.
   402     self close.
   396     ^ stream contents
   403     ^ stream contents
   397 !
   404 !
   398 
   405 
   433 	offset > n ifTrue:[^ data]
   440 	offset > n ifTrue:[^ data]
   434     ].
   441     ].
   435     ^ data copyFrom:1 to:(offset - 1)
   442     ^ data copyFrom:1 to:(offset - 1)
   436 !
   443 !
   437 
   444 
   438 skip:count 
   445 skip:count
   439     "skip count objects, return the receiver
   446     "skip count objects, return the receiver
   440      redefined for optimization"
   447      redefined for optimization"
   441 
   448 
   442     |n avail|
   449     |n avail|
   443 
   450 
   444     n := count.
   451     n := count.
   445 
   452 
   446     n <= 0 ifTrue:[
   453     n <= 0 ifTrue:[
   447         n ~~ 0 ifTrue:[
   454 	n ~~ 0 ifTrue:[
   448             "dont know how to unread ..."
   455 	    "dont know how to unread ..."
   449             PositionError raiseRequest
   456 	    PositionError raiseRequest
   450         ].
   457 	].
   451         ^ self
   458 	^ self
   452     ].
   459     ].
   453 
   460 
   454     [self canReadWithoutBlocking] whileTrue:[
   461     [self canReadWithoutBlocking] whileTrue:[
   455         avail := readLimit - position.
   462 	avail := readLimit - position.
   456 
   463 
   457         avail >= n ifTrue:[
   464 	avail >= n ifTrue:[
   458             position := position + n.
   465 	    position := position + n.
   459             ^ self
   466 	    ^ self
   460         ].
   467 	].
   461         position := readLimit := 0. "/ reset input
   468 	position := readLimit := 0. "/ reset input
   462         n := n - avail.
   469 	n := n - avail.
   463     ].
   470     ].
   464 ! !
   471 ! !
   465 
   472 
   466 !CompressionStream methodsFor:'startup & release'!
   473 !CompressionStream methodsFor:'startup & release'!
   467 
   474 
   483     ^ self streamOpenWithMode:aMode on:aStream.
   490     ^ self streamOpenWithMode:aMode on:aStream.
   484 !
   491 !
   485 
   492 
   486 streamOpenWithMode:aMode on:aStream
   493 streamOpenWithMode:aMode on:aStream
   487     "open the compression stream on a stream
   494     "open the compression stream on a stream
   488          #readonly    uncompress the data derived from the read-stream,  aStream
   495 	 #readonly    uncompress the data derived from the read-stream,  aStream
   489          #writeonly   compress   the data and write to the write-stream, aStream
   496 	 #writeonly   compress   the data and write to the write-stream, aStream
   490     "
   497     "
   491 
   498 
   492     aStream isNil ifTrue:[
   499     aStream isNil ifTrue:[
   493         ^ self errorNotOpen
   500 	^ self errorNotOpen
   494     ].
   501     ].
   495 
   502 
   496     onStream    := aStream.    
   503     onStream    := aStream.
   497     mode        := aMode.
   504     mode        := aMode.
   498     outputBytes := ExternalBytes unprotectedNew:16384.
   505     outputBytes := ExternalBytes unprotectedNew:16384.
   499     inputBytes  := ExternalBytes unprotectedNew:16384.
   506     inputBytes  := ExternalBytes unprotectedNew:16384.
   500     readLimit   := position := 0.
   507     readLimit   := position := 0.
   501     binary      := false.
   508     binary      := false.
   504     self registerForFinalization.
   511     self registerForFinalization.
   505 
   512 
   506     hitEOF := false.
   513     hitEOF := false.
   507 
   514 
   508     aMode == #readonly ifTrue:[
   515     aMode == #readonly ifTrue:[
   509         self zinflateInit.
   516 	self zinflateInit.
   510     ] ifFalse:[
   517     ] ifFalse:[
   511         self zdeflateInit
   518 	self zdeflateInit
   512     ].
   519     ].
   513 ! !
   520 ! !
   514 
   521 
   515 !CompressionStream methodsFor:'writing'!
   522 !CompressionStream methodsFor:'writing'!
   516 
   523 
   530     self zset_avail_in:position.
   537     self zset_avail_in:position.
   531 
   538 
   532     position := 0.
   539     position := 0.
   533 
   540 
   534     [   continue := self zdeflate.
   541     [   continue := self zdeflate.
   535         availOut := self zget_avail_out.
   542 	availOut := self zget_avail_out.
   536 
   543 
   537         availOut > 0 ifTrue:[
   544 	availOut > 0 ifTrue:[
   538             self onStreamPutBytes:availOut from:outputBytes
   545 	    self onStreamPutBytes:availOut from:outputBytes
   539         ].
   546 	].
   540 
   547 
   541     ] doWhile:[ continue == true ].
   548     ] doWhile:[ continue == true ].
   542 !
   549 !
   543 
   550 
   544 nextPut:aByteOrCharacter
   551 nextPut:aByteOrCharacter
   553     |limit|
   560     |limit|
   554 
   561 
   555     limit := inputBytes size.
   562     limit := inputBytes size.
   556 
   563 
   557     aCollection do:[:aByteOrCharacter|
   564     aCollection do:[:aByteOrCharacter|
   558         position == limit ifTrue:[self flush].
   565 	position == limit ifTrue:[self flush].
   559         position := position + 1.
   566 	position := position + 1.
   560         inputBytes at:position put:aByteOrCharacter asInteger.
   567 	inputBytes at:position put:aByteOrCharacter asInteger.
   561     ].
   568     ].
   562     ^ aCollection
   569     ^ aCollection
   563 ! !
   570 ! !
   564 
   571 
   565 !CompressionStream class methodsFor:'documentation'!
   572 !CompressionStream class methodsFor:'documentation'!
   566 
   573 
   567 version
   574 version
   568     ^ '$Header: /cvs/stx/stx/libbasic2/CompressionStream.st,v 1.22 2008-06-05 09:15:06 ab Exp $'
   575     ^ '$Header: /cvs/stx/stx/libbasic2/CompressionStream.st,v 1.23 2009-07-31 11:16:42 cg Exp $'
   569 ! !
   576 ! !
   570 
   577 
   571 CompressionStream initialize!
   578 CompressionStream initialize!