Documentation. Does not work yet.
authorStefan Vogel <sv@exept.de>
Wed, 07 May 2003 10:11:05 +0200
changeset 1197 c86e858c2893
parent 1196 bba6d37ed88b
child 1198 1d64321c7afc
Documentation. Does not work yet.
CompressionStream.st
ZipStream.st
--- a/CompressionStream.st	Tue May 06 18:29:40 2003 +0200
+++ b/CompressionStream.st	Wed May 07 10:11:05 2003 +0200
@@ -8,6 +8,23 @@
 	category:'System-Compress'
 !
 
+!CompressionStream class methodsFor:'documentation'!
+
+documentation
+"
+    Abstract superclass of streams that compress or deconpress data
+
+    [author:]
+        Claus Atzkern
+
+    [instance variables:]
+
+    [class variables:]
+
+    [see also:]
+
+"
+! !
 
 !CompressionStream class methodsFor:'initialization'!
 
@@ -17,21 +34,15 @@
 
 !CompressionStream class methodsFor:'instance creation'!
 
-openWithMode:modeSymbol on:aStream
-    "open on aStream with mode modeSymbol (#readonly #writeonly)"
+readOpenOn:aStream
+    "open to read data from an compressed stream"
 
-    ^ self subclassResponsibility
-!
-
-readOpenOn:aStream
-    "read data from an compressed stream
-    "
     ^ self basicNew openWithMode:#readonly on:aStream
 !
 
 writeOpenOn:aStream
-    "write data compressed to stream 
-    "
+    "open to write data compressed to stream"
+
     ^ self basicNew openWithMode:#writeonly on:aStream
 ! !
 
@@ -47,38 +58,38 @@
    file isReadable ifFalse:[^ self error:'not existant'].
 
    time := Time millisecondsToRun:[ |zipStream|
-	zipStream := stream := zipCont := nil.
-	[
-	    stream    := file readStream.
-	    zipStream := ZipStream readOpenOn:stream.
-	    zipCont   := zipStream contents.
-	] valueNowOrOnUnwindDo:[
-	    zipStream notNil ifTrue:[zipStream close].
-	    stream    notNil ifTrue:[stream close].
-	].
+        zipStream := stream := zipCont := nil.
+        [
+            stream    := file readStream.
+            zipStream := ZipStream readOpenOn:stream.
+            zipCont   := zipStream contents.
+        ] valueNowOrOnUnwindDo:[
+            zipStream notNil ifTrue:[zipStream close].
+            stream    notNil ifTrue:[stream close].
+        ].
    ].
    Transcript showCR:('STX   Time : %1  Size: %2' bindWith:time with:(zipCont size)).
 
    time := Time millisecondsToRun:[ |zipStream wstream|
-	zipStream := stream := nxtCont := nil.
-	[
-	    stream    := file readStream.
-	    wstream   := '' writeStream.
-	    zipStream := ZipStream readOpenOn:stream.
+        zipStream := stream := nxtCont := nil.
+        [
+            stream    := file readStream.
+            wstream   := '' writeStream.
+            zipStream := ZipStream readOpenOn:stream.
 
-	    [zipStream atEnd] whileFalse:[
-		wstream nextPutAll:(zipStream next:117)
-	    ].
-	    nxtCont := wstream contents.
-	] valueNowOrOnUnwindDo:[
-	    zipStream notNil ifTrue:[zipStream close].
-	    stream    notNil ifTrue:[stream close].
-	].
+            [zipStream atEnd] whileFalse:[
+                wstream nextPutAll:(zipStream next:117)
+            ].
+            nxtCont := wstream contents.
+        ] ensure:[
+            zipStream notNil ifTrue:[zipStream close].
+            stream    notNil ifTrue:[stream close].
+        ].
    ].
    Transcript showCR:('NEXT  Time : %1  Size: %2' bindWith:time with:(nxtCont size)).
 
    nxtCont = zipCont ifTrue:[ Transcript showCR:'OK' ]
-		    ifFalse:[ self error:'contents differs' ].
+                    ifFalse:[ self error:'contents differs' ].
 !
 
 doTestSkipN
@@ -93,46 +104,45 @@
    skip := 6885379.
 
    time := Time millisecondsToRun:[ |zipStream wstream|
-	zipStream := stream := nxtCont := nil.
-	[
-	    stream    := file readStream.
-	    wstream   := '' writeStream.
-	    zipStream := ZipStream readOpenOn:stream.
-	    skip timesRepeat:[ zipStream next ].
+        zipStream := stream := nxtCont := nil.
+        [
+            stream    := file readStream.
+            wstream   := '' writeStream.
+            zipStream := ZipStream readOpenOn:stream.
+            skip timesRepeat:[ zipStream next ].
 
-	    [zipStream atEnd] whileFalse:[
-		wstream nextPutAll:(zipStream next:117)
-	    ].
-	    nxtCont := wstream contents.
-	] valueNowOrOnUnwindDo:[
-	    zipStream notNil ifTrue:[zipStream close].
-	    stream    notNil ifTrue:[stream close].
-	].
+            [zipStream atEnd] whileFalse:[
+                wstream nextPutAll:(zipStream next:117)
+            ].
+            nxtCont := wstream contents.
+        ] ensure:[
+            zipStream notNil ifTrue:[zipStream close].
+            stream    notNil ifTrue:[stream close].
+        ].
    ].
 
    Transcript showCR:('STX   Time : %1  Size: %2' bindWith:time with:(nxtCont size)).
 
    time := Time millisecondsToRun:[ |zipStream wstream|
-	zipStream := stream := skpCont := nil.
-	[
-	    stream    := file readStream.
-	    wstream   := '' writeStream.
-	    zipStream := ZipStream readOpenOn:stream.
-	    zipStream skip:skip.
-	    [zipStream atEnd] whileFalse:[
-		wstream nextPutAll:(zipStream next:117)
-	    ].
-	    skpCont := wstream contents.
-	] valueNowOrOnUnwindDo:[
-	    zipStream notNil ifTrue:[zipStream close].
-	    stream    notNil ifTrue:[stream close].
-	].
+        zipStream := stream := skpCont := nil.
+        [
+            stream    := file readStream.
+            wstream   := '' writeStream.
+            zipStream := ZipStream readOpenOn:stream.
+            zipStream skip:skip.
+            [zipStream atEnd] whileFalse:[
+                wstream nextPutAll:(zipStream next:117)
+            ].
+            skpCont := wstream contents.
+        ] valueNowOrOnUnwindDo:[
+            zipStream notNil ifTrue:[zipStream close].
+            stream    notNil ifTrue:[stream close].
+        ].
    ].
    Transcript showCR:('NEXT  Time : %1  Size: %2' bindWith:time with:(skpCont size)).
 
    nxtCont = skpCont ifTrue:[ Transcript showCR:'OK' ]
-		    ifFalse:[ self error:'contents differs' ].
-
+                    ifFalse:[ self error:'contents differs' ].
 !
 
 doTestUnixAgainstClass
@@ -145,38 +155,38 @@
    file isReadable ifFalse:[^ self error:'not existant'].
 
    time := Time millisecondsToRun:[ |zipStream|
-	zipStream := stream := zipCont := nil.
-	[
-	    stream    := file readStream.
-	    zipStream := ZipStream readOpenOn:stream.
-	    zipCont   := zipStream contents.
-	] valueNowOrOnUnwindDo:[
-	    zipStream notNil ifTrue:[zipStream close].
-	    stream    notNil ifTrue:[stream close].
-	].
+        zipStream := stream := zipCont := nil.
+        [
+            stream    := file readStream.
+            zipStream := ZipStream readOpenOn:stream.
+            zipCont   := zipStream contents.
+        ] ensure:[
+            zipStream notNil ifTrue:[zipStream close].
+            stream    notNil ifTrue:[stream close].
+        ].
    ].
    Transcript showCR:('STX   Time : %1  Size: %2' bindWith:time with:(zipCont size)).
 
    time := Time millisecondsToRun:[ |command|
-	cmdCont := stream := nil.
-	[
-	    command := 'gunzip < ' , file pathName.
-	    stream  := PipeStream readingFrom:command.
-	    cmdCont := stream contentsOfEntireFile.
+        cmdCont := stream := nil.
+        [
+            command := 'gunzip < ' , file pathName.
+            stream  := PipeStream readingFrom:command.
+            cmdCont := stream contentsOfEntireFile.
 
-	] valueNowOrOnUnwindDo:[
-	    stream notNil ifTrue:[stream close].
-	]
+        ] valueNowOrOnUnwindDo:[
+            stream notNil ifTrue:[stream close].
+        ]
    ].
    Transcript showCR:('UNIX  Time : %1  Size: %2' bindWith:time with:(cmdCont size)).
 
    cmdCont = zipCont ifTrue:[ Transcript showCR:'OK' ]
-		    ifFalse:[ self error:'contents differs' ].
+                    ifFalse:[ self error:'contents differs' ].
 !
 
 test
 "
-CompressionStream test
+BZip2Stream test
 "
    |original compressed contents in out zip|
 
@@ -185,39 +195,39 @@
    in := original readStream.
 
    [ |b|
-	out := #[] writeStream.
-	zip := self writeOpenOn:out.
+        out := #[] writeStream.
+        zip := self writeOpenOn:out.
 
-	[in atEnd] whileFalse:[
-	    (b := in next) ifNotNil:[zip nextPut:b]
-	]
-   ] valueNowOrOnUnwindDo:[ zip ifNotNil:[ zip close ] ].
+        [in atEnd] whileFalse:[
+            zip nextPut:in next
+        ]
+   ] ensure:[ zip notNil ifTrue:[ zip close ] ].
 
    compressed := out contents.
    [ |b|
-	zip := self readOpenOn:(compressed readStream).
-	out := '' writeStream.
+        zip := self readOpenOn:(compressed readStream).
+        out := '' writeStream.
 
-	[ (b := zip next) notNil ] whileTrue:[ out nextPut:b ]
+        [ (b := zip next) notNil ] whileTrue:[ out nextPut:b ]
 
-   ] valueNowOrOnUnwindDo:[
-	zip ifNotNil:[ zip close ].
-	contents := out contents.
+   ] ensure:[
+        zip notNil ifTrue:[ zip close ].
+        contents := out contents.
 
-	Transcript showCR:(contents   size).
-	Transcript showCR:(compressed size).
+        Transcript showCR:(contents   size).
+        Transcript showCR:(compressed size).
    ].
 
    original = contents ifFalse:[
-	self halt:'contents differs'.
-      ^ self
+        self error:'contents differs'.
+        ^ self
    ].
    Transcript showCR:'OK'.
 !
 
 testFile
 "
-CompressionStream testFile
+ZipStream testFile
 "
    |fileContents in zip out gzipCmd|
 
@@ -227,17 +237,18 @@
    out := FileStream newFileNamed:'YYY.gz'.
    out ifNil:[ ^ self ].
 
-   [ zip := self writeOpenOn:out.
+   [ 
+      zip := self writeOpenOn:out.
 
      [in atEnd] whileFalse:[ |buf|
-	buf := in nextAvailable:512.
-	buf do:[:n|
-	    zip nextPut:n
-	]
+        buf := in nextAvailable:512.
+        buf do:[:n|
+            zip nextPut:n
+        ]
      ].
-   ] valueNowOrOnUnwindDo:[
-	zip ifNotNil:[ zip close ].
-	out close.
+   ] ensure:[
+        zip notNil ifTrue:[ zip close ].
+        out close.
    ].
    gzipCmd := 'gzip -dc YYY.gz > YYY; diff YYY smalltalk.rc'.
 
@@ -293,25 +304,24 @@
     |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
+        ].
     ].
-    self closeZStream.
-    Stream streamErrorSignal raiseErrorString:(self class name , ': ', error).
+    StreamError raiseErrorString:(self class name , ': ', error).
 ! !
 
 !CompressionStream methodsFor:'finalization'!
@@ -470,7 +480,6 @@
 onStreamPutBytes:count from:data
     "write compressed data to the (output) stream"
 
-    onStream isNil ifTrue:[self errorNotOpen].
     onStream nextPutBytes:count from:data startingAt:1
 ! !
 
@@ -488,24 +497,26 @@
      updates the readLimit and position"
 
     mode == #readonly ifFalse:[
-	self errorReadOnly
+        self errorWriteOnly
     ].
-    hitEOF == true ifTrue:[ ^ false ].
+    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.
+        [(readLimit := self zinflate) == 0] whileTrue:[ 
+            |n|
+            n := onStream nextBytes:(inputBytes size) into:inputBytes startingAt:1.
+            n == 0 ifTrue:[
+                hitEOF := true.
+                ^ false
+"/                self pastEnd
+            ].
+            self zset_avail_in:n.
+        ].
+        readLimit isNil ifTrue:[
+            hitEOF := true.
+            ^ false
+        ].
+        position := 0.
     ].
     ^ true
 !
@@ -542,23 +553,25 @@
 
     |species stream bfsize buffer count|
 
-    mode == #readonly ifFalse:[ self errorReadOnly ].
+    mode == #readonly ifFalse:[
+        self errorWriteOnly
+    ].
     bfsize := outputBytes size.
 
     species := self contentsSpecies.
     buffer  := species new:bfsize.
     stream  := (species new:bfsize) writeStream.
 
-    [ self canReadWithoutBlocking ] whileTrue:[
-	count := self z_nextAvailableInto:buffer startingAt:1.
+    [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)
-	    ]
-	].
+        count == bfsize ifTrue:[
+            stream nextPutAll:buffer.
+        ] ifFalse:[
+            count > 0 ifTrue:[    
+                stream nextPutAll:buffer startingAt:1 to:count.
+            ]
+        ].
     ].
     self close.
     ^ stream contents
@@ -645,11 +658,15 @@
 
 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
+         #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 ].
 
+    aStream isNil ifTrue:[
+        ^ self errorNotOpen
+    ].
+
+    onStream := aStream.    
     mode        := aMode.
     outputBytes := ExternalBytes unprotectedNew:8192.
     inputBytes  := ExternalBytes unprotectedNew:8192.
@@ -662,9 +679,9 @@
     hitEOF := false.
 
     aMode == #readonly ifTrue:[
-	self zinflateInit.
+        self zinflateInit.
     ] ifFalse:[
-	self zdeflateInit
+        self zdeflateInit
     ].
 ! !
 
@@ -682,20 +699,20 @@
 
     |continue|
 
-    self isWritable ifFalse:[ ^ self ].
+    self isWritable 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.
-    ].
+    [ 
+        |count|
+        continue := self zdeflate.
+        count := self zget_avail_out.
+
+        count > 0 ifTrue:[
+            self onStreamPutBytes:count from:outputBytes
+        ].
+    ] doWhile:continue.
 !
 
 nextPut:aByteOrCharacter
@@ -709,7 +726,7 @@
 !CompressionStream class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic2/CompressionStream.st,v 1.10 2003-05-06 16:19:20 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic2/CompressionStream.st,v 1.11 2003-05-07 08:11:05 stefan Exp $'
 ! !
 
 CompressionStream initialize!
--- a/ZipStream.st	Tue May 06 18:29:40 2003 +0200
+++ b/ZipStream.st	Wed May 07 10:11:05 2003 +0200
@@ -41,6 +41,42 @@
 %}
 ! !
 
+!ZipStream class methodsFor:'documentation'!
+
+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'!
 
@@ -425,69 +461,69 @@
 !ZipStream methodsFor:'startup & release'!
 
 openWithMode:aMode on:aStream
+
     super openWithMode:aMode on:aStream.
-
     self isReadable ifTrue:[
-	"Check for the gzip magic id"
-	|flags|
+        "Check for the gzip magic id"
+        |flags|
 
-	GZ_MAGIC_ID do:[:b|
-	    onStream nextByte ~~ b ifTrue:[ self zerror:'version error' ]
-	].
+        GZ_MAGIC_ID do:[:b|
+            onStream nextByte ~~ b ifTrue:[ self zerror:'version error' ]
+        ].
 
-	onStream nextByte ~~ Z_DEFLATED ifTrue:[
-	    self zerror:'invalid method (not deflated)'
-	].
+        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'
-	].
+        flags := onStream nextByte.
+        (flags bitAnd:HEAD_RESERVED) ~~ 0 ifTrue:[
+            self zerror:'wrong data format'
+        ].
 
-	"discard time, xflags and OS code"
-	onStream skip:6.
+        "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_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_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.
-	].
+        (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 gzip magic id
+        "
+        GZ_MAGIC_ID do:[:b| onStream nextPutByte:b ].
 
-	"write the method"
-	onStream nextPutByte:Z_DEFLATED.
+        "write the method"
+        onStream nextPutByte:Z_DEFLATED.
 
-	"write the flags"
-	onStream nextPutByte:0.
+        "write the flags"
+        onStream nextPutByte:0.
 
-	"write time"
-	4 timesRepeat:[ onStream nextPutByte:0 ].
+        "write time"
+        4 timesRepeat:[ onStream nextPutByte:0 ].
 
-	"write xflags"
-	onStream nextPutByte:0.
+        "write xflags"
+        onStream nextPutByte:0.
 
-	"write OS code"
-	onStream nextPutByte:HEAD_OS_CODE.
+        "write OS code"
+        onStream nextPutByte:HEAD_OS_CODE.
     ].    
 ! !
 
 !ZipStream class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic2/ZipStream.st,v 1.19 2003-05-06 16:19:20 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic2/ZipStream.st,v 1.20 2003-05-07 08:10:24 stefan Exp $'
 ! !
 
 ZipStream initialize!