CompressionStream.st
changeset 2190 6c3f9241753a
parent 2005 a6ef1083aa32
child 2191 7cb40c5e5511
--- a/CompressionStream.st	Mon Jul 27 18:04:15 2009 +0200
+++ b/CompressionStream.st	Fri Jul 31 13:16:42 2009 +0200
@@ -1,6 +1,6 @@
 "
  COPYRIGHT (c) 2002 by eXept Software AG
-              All Rights Reserved
+	      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
@@ -24,7 +24,7 @@
 copyright
 "
  COPYRIGHT (c) 2002 by eXept Software AG
-              All Rights Reserved
+	      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
@@ -40,7 +40,7 @@
     Abstract superclass of streams that compress or deconpress data
 
     [author:]
-        Claus Atzkern
+	Claus Atzkern
 
     [instance variables:]
 
@@ -122,22 +122,22 @@
     |error|
 
     zstream isNil ifTrue:[
-        error := 'not open'.
+	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
-        ].
+	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).
 ! !
@@ -145,10 +145,10 @@
 !CompressionStream methodsFor:'finalization'!
 
 executor
-    "redefined to return a lightweight copy 
+    "redefined to return a lightweight copy
      - all we need is the memory handle"
 
-    ^ self class basicNew finalizeCopy:zstream.    
+    ^ self class basicNew finalizeCopy:zstream.
 !
 
 finalize
@@ -166,7 +166,7 @@
 
 !CompressionStream methodsFor:'low level'!
 
-z_nextAvailableInto:aCollection startingAt:offset
+z_nextAvailableInto:aCollection startingAt:offset maxCount:maxCount
     "read the next available bytes into a collection, a string or byteArray;
      returns the size read"
 
@@ -177,14 +177,17 @@
 
     count := aCollection size - offset + 1.
 
-    count > 0 ifFalse:[
-	count < 0 ifTrue:[
-	    self zerror:'invalid arguments'
-	].
+    count < 0 ifTrue:[
+	self zerror:'invalid arguments'
+    ].
+    count == 0 ifTrue:[
 	^ 0
     ].
-    count    := avail min:count.
-    start    := position.
+
+    count := avail min:count.
+    maxCount notNil ifTrue:[ count := count min:maxCount ].
+
+    start := position.
     position := position + count.
 
 %{  unsigned char * _dstPt;
@@ -219,6 +222,10 @@
     ^ self zerror:'invalid argument'
 !
 
+z_nextAvailableInto:aCollection startingAt:offset
+    ^ self z_nextAvailableInto:aCollection startingAt:offset maxCount:nil
+!
+
 zclose
     "low level close of the zip stream"
 
@@ -317,25 +324,25 @@
     |n|
 
     mode == #readonly ifFalse:[
-        self errorWriteOnly
+	self errorWriteOnly
     ].
     hitEOF == true ifTrue:[^ false].
 
     position >= readLimit ifTrue:[
-        [(readLimit := self zinflate) == 0] whileTrue:[ 
-            n := onStream nextBytes:(inputBytes size) into:inputBytes startingAt:1.
+	[(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.
+	    n == 0 ifTrue:[
+		hitEOF := true.
+		^ false
+	    ].
+	    self zset_avail_in:n.
+	].
+	readLimit isNil ifTrue:[
+	    hitEOF := true.
+	    ^ false
+	].
+	position := 0.
     ].
     ^ true
 !
@@ -373,7 +380,7 @@
     |species stream bfsize buffer count|
 
     mode == #readonly ifFalse:[
-        self errorWriteOnly
+	self errorWriteOnly
     ].
     bfsize := outputBytes size.
 
@@ -382,15 +389,15 @@
     stream  := WriteStream on:(species new:bfsize).
 
     [self canReadWithoutBlocking] whileTrue:[
-        count := self z_nextAvailableInto:buffer startingAt:1.
+	count := self z_nextAvailableInto:buffer startingAt:1.
 
-        count == bfsize ifTrue:[
-            stream nextPutAll:buffer.
-        ] ifFalse:[
-            count > 0 ifTrue:[    
-                stream nextPutAll:buffer startingAt:1 to:count.
-            ]
-        ].
+	count == bfsize ifTrue:[
+	    stream nextPutAll:buffer.
+	] ifFalse:[
+	    count > 0 ifTrue:[
+		stream nextPutAll:buffer startingAt:1 to:count.
+	    ]
+	].
     ].
     self close.
     ^ stream contents
@@ -435,7 +442,7 @@
     ^ data copyFrom:1 to:(offset - 1)
 !
 
-skip:count 
+skip:count
     "skip count objects, return the receiver
      redefined for optimization"
 
@@ -444,22 +451,22 @@
     n := count.
 
     n <= 0 ifTrue:[
-        n ~~ 0 ifTrue:[
-            "dont know how to unread ..."
-            PositionError raiseRequest
-        ].
-        ^ self
+	n ~~ 0 ifTrue:[
+	    "dont know how to unread ..."
+	    PositionError raiseRequest
+	].
+	^ self
     ].
 
     [self canReadWithoutBlocking] whileTrue:[
-        avail := readLimit - position.
+	avail := readLimit - position.
 
-        avail >= n ifTrue:[
-            position := position + n.
-            ^ self
-        ].
-        position := readLimit := 0. "/ reset input
-        n := n - avail.
+	avail >= n ifTrue:[
+	    position := position + n.
+	    ^ self
+	].
+	position := readLimit := 0. "/ reset input
+	n := n - avail.
     ].
 ! !
 
@@ -485,15 +492,15 @@
 
 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
+	 #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
+	^ self errorNotOpen
     ].
 
-    onStream    := aStream.    
+    onStream    := aStream.
     mode        := aMode.
     outputBytes := ExternalBytes unprotectedNew:16384.
     inputBytes  := ExternalBytes unprotectedNew:16384.
@@ -506,9 +513,9 @@
     hitEOF := false.
 
     aMode == #readonly ifTrue:[
-        self zinflateInit.
+	self zinflateInit.
     ] ifFalse:[
-        self zdeflateInit
+	self zdeflateInit
     ].
 ! !
 
@@ -532,11 +539,11 @@
     position := 0.
 
     [   continue := self zdeflate.
-        availOut := self zget_avail_out.
+	availOut := self zget_avail_out.
 
-        availOut > 0 ifTrue:[
-            self onStreamPutBytes:availOut from:outputBytes
-        ].
+	availOut > 0 ifTrue:[
+	    self onStreamPutBytes:availOut from:outputBytes
+	].
 
     ] doWhile:[ continue == true ].
 !
@@ -555,9 +562,9 @@
     limit := inputBytes size.
 
     aCollection do:[:aByteOrCharacter|
-        position == limit ifTrue:[self flush].
-        position := position + 1.
-        inputBytes at:position put:aByteOrCharacter asInteger.
+	position == limit ifTrue:[self flush].
+	position := position + 1.
+	inputBytes at:position put:aByteOrCharacter asInteger.
     ].
     ^ aCollection
 ! !
@@ -565,7 +572,7 @@
 !CompressionStream class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic2/CompressionStream.st,v 1.22 2008-06-05 09:15:06 ab Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic2/CompressionStream.st,v 1.23 2009-07-31 11:16:42 cg Exp $'
 ! !
 
 CompressionStream initialize!