ZipArchive.st
changeset 2176 141e6b175455
parent 2173 254452034748
child 2180 ed0c36ab24b8
--- a/ZipArchive.st	Tue Jun 30 17:28:52 2009 +0200
+++ b/ZipArchive.st	Tue Jun 30 17:32:14 2009 +0200
@@ -28,6 +28,14 @@
 	category:'System-Support-FileFormats'
 !
 
+PeekableStream subclass:#AbstractZipStream
+	instanceVariableNames:'zipArchive zipEntry zipFileStream compressingStream crc32
+		uncompressedDataSize startDataPosition'
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:ZipArchive
+!
+
 Object subclass:#ZipCentralDirectory
 	instanceVariableNames:'numberOfThisDisk centralDirectoryStartDiskNumber
 		centralDirectoryTotalNoOfEntriesOnThisDisk
@@ -51,6 +59,20 @@
 	privateIn:ZipArchive
 !
 
+ZipArchive::AbstractZipStream subclass:#ZipReadStream
+	instanceVariableNames:'readPosition peek'
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:ZipArchive
+!
+
+ZipArchive::AbstractZipStream subclass:#ZipWriteStream
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:ZipArchive
+!
+
 !ZipArchive primitiveDefinitions!
 %{
 
@@ -3026,6 +3048,10 @@
 
 !ZipArchive class methodsFor:'constants'!
 
+COMPR_DEFLATED
+    ^ COMPR_DEFLATED
+!
+
 LREC_SIZE
     ^ LREC_SIZE
 
@@ -3152,130 +3178,6 @@
 
 !ZipArchive methodsFor:'private'!
 
-addContentsToArchiveFrom: realFileName to: zipFileName compress: aCompressFlag
-    <resource: #obsolete>
-    |fromStream zipEntry data archiveData curTime curDate theCompressMethod positionSize
-     theZipFileName |
-
-    "/ sr & cg:
-    "/ is this obsolete ?
-    "/
-    "/ if not, please refactor by calling
-    "/    self addFile: aFileName fromStream: aStream compressMethod: (aCompressFlag ifTrue:COMPR_DEFLATED ifFalse:COMPR_STORED) asDirectory:false
-    "/ as this is no longer sent, is it still needed ????
-
-    aCompressFlag ifTrue: [
-        fromStream := realFileName readStream.
-        theCompressMethod := COMPR_DEFLATED.
-    ] ifFalse: [
-        fromStream := realFileName readStream.
-        theCompressMethod := COMPR_STORED.
-    ].
-
-    fromStream isNil ifTrue: [
-        ^ self error: 'Could not open: ', realFileName name,' for reading ...'.
-    ].
-
-    (file isNil or: [mode ~~ #write]) ifTrue: [
-        ^ self error: 'Archiv not open for writing ...'.
-    ].
-
-    zipEntry := ZipMember new default.
-
-    firstEntry isNil ifTrue: [
-        firstEntry := zipEntry.
-    ] ifFalse: [
-        lastEntry next: zipEntry.
-    ].
-
-    lastEntry := zipEntry.
-
-    theZipFileName := self validZipFileNameFrom:zipFileName. 
-
-    zipEntry fileName: theZipFileName.
-    zipEntry fileNameLength: theZipFileName size.
-    zipEntry uncompressedSize: 0.
-
-    zipEntry compressionMethod: theCompressMethod.
-    zipEntry internalFileAttributes: 1.
-    zipEntry externalFileAttributes: EXTERNALFILEATTRIBUTES_ISFILE.
-
-    curTime := Time now.
-    curDate := Date today.
-    "/ data and time in msdos format
-    zipEntry lastModFileTime: (((curTime seconds // 2) bitOr: (curTime minutes rightShift: -5)) bitOr: (curTime hours rightShift: -11)).
-    zipEntry lastModFileDate: (((curDate day) bitOr: (curDate month rightShift: -5)) bitOr: (((curDate year) - 1980) rightShift: -9)).
-
-    data notEmptyOrNil ifTrue: [     
-        "/ crc32 is allways reqired (not as written in docu to be zero in case of uncompressed mode)
-        zipEntry crc32: (ZipStream crc32BytesIn: data).
-    ].
-
-    (theCompressMethod == COMPR_DEFLATED) ifTrue: [
-        |tmpCompressedData tmpCompressedDataSize|
-
-        tmpCompressedData := ByteArray new:(data size + 16). "/ if the compression is less then the additional overhead we need more space in buffer
-        tmpCompressedDataSize := ZipStream compress:data into:tmpCompressedData.
-
-        zipEntry compressedSize: (tmpCompressedDataSize - 6). "/6 = the zlib specific data 2 bytes in front and 4 bytes behind the real data
-        archiveData := tmpCompressedData copyFrom: 3. "/ 2 bytes before the real data
-    ] ifFalse: [
-        zipEntry compressedSize: zipEntry uncompressedSize.
-        archiveData := data.
-    ].
-
-    "/ ensure that the file position is at the end
-    file setToEnd.
-
-    zipEntry relativeLocalHeaderOffset:(file position).
-    file nextPutLong: 16r04034b50  MSB:false.
-    file nextPutShort:zipEntry versionNeedToExtract MSB:false.
-    file nextPutShort:zipEntry generalPurposBitFlag MSB:false.
-    file nextPutShort:zipEntry compressionMethod MSB:false.
-    file nextPutShort:zipEntry lastModFileTime MSB:false.
-    file nextPutShort:zipEntry lastModFileDate MSB:false.
-    file nextPutLong:zipEntry crc32 MSB:false.
-    "/ remember the position where the size of the data should be written
-    positionSize := file position.
-    file nextPutLong:zipEntry compressedSize MSB:false.
-    file nextPutLong:zipEntry uncompressedSize MSB:false.
-    file nextPutShort:zipEntry fileNameLength MSB:false.
-    file nextPutShort:zipEntry extraFieldLength MSB:false.
-    file nextPutAll:zipEntry fileName.
-    zipEntry extraField notNil ifTrue: [
-        file nextPutAll:zipEntry extraField.
-    ].
-
-    archiveData notNil ifTrue: [
-        file nextPutBytes: zipEntry compressedSize from: archiveData.
-    ].
-
-    zipEntry compressedSize: data size.
-    zipEntry uncompressedSize: data size.
-
-    " set filepointer back to position where the size of the contents should be written
-    "
-    file position: positionSize.
-
-    file nextPutLong:zipEntry compressedSize MSB:false.
-    file nextPutLong:zipEntry uncompressedSize MSB:false.
-
-    file setToEnd.
-    ^ true
-!
-
-addFile: aFileName withContents: data compressed: doCompressFlag
-    <resource: #obsolete>
-    "/ sr & cg:
-    "/ is this obsolete ?
-
-    ^ self 
-        addFile: aFileName 
-        withContents: data 
-        compressMethod:(doCompressFlag ifTrue:COMPR_DEFLATED ifFalse:COMPR_STORED)
-        asDirectory: false.
-!
-
 checkZipArchive:archiveFileName
     |isValidArchive|
 
@@ -3600,14 +3502,12 @@
 readDirectory
     "read the zip directory into a linked-list of zipMembers"
 
-    |size count_in pos0 dataString|
+    |size pos0|
 
     self setDefaultArchiveBounds.
 
-"/    size := file fileSize.
     size := endOfArchive - startOfArchive.
     (size == 0) ifTrue:[
-        count_in := 0.
         ^ self
     ].
 
@@ -3624,129 +3524,51 @@
 
     "/ Now we have found the end of central directory record
     centralDirectory := ZipCentralDirectory new.
-    centralDirectory numberOfThisDisk:(file nextUnsignedShortMSB:false).
-    centralDirectory centralDirectoryStartDiskNumber:(file nextUnsignedShortMSB:false).
-    centralDirectory centralDirectoryTotalNoOfEntriesOnThisDisk:(file nextUnsignedShortMSB:false).
-    centralDirectory centralDirectoryTotalNoOfEntries:(file nextUnsignedShortMSB:false).
-    centralDirectory centralDirectorySize:(file nextLongMSB:false).
-    centralDirectory centralDirectoryStartOffset:(file nextLongMSB:false).
-    centralDirectory zipCommentLength:(file nextUnsignedShortMSB:false).
-    centralDirectory zipCommentLength ~~ 0 ifTrue: [
-        "/ read zip comment
-        centralDirectory zipComment:(dataString := String new:(centralDirectory zipCommentLength)).
-        file nextBytes:(centralDirectory zipCommentLength) into:dataString.
-    ].
-
-    "/ set file position to start of central directory
-    (pos0 - (centralDirectory centralDirectorySize)) < startOfArchive ifTrue: [
-        ^ ZipFileFormatErrorSignal raiseRequestErrorString:' - central directory start is out of the archive bounds'.
-    ].
-
-    file position0Based:(pos0 - (centralDirectory centralDirectorySize)).
-    count_in := centralDirectory centralDirectoryTotalNoOfEntries.
-
     EndOfStreamNotification handle:[:ex|
-        self warn:'ZipArchive: file format error or short file: ' ,
-            (file isFileStream ifTrue:[file pathName] ifFalse:['inStream']).
+        ZipFileFormatErrorSignal raiseRequestErrorString:' - file format error or short file: ' ,
+                                        (file isFileStream ifTrue:[file pathName] ifFalse:['inStream']).
         ^ self.
     ] do:[
+        centralDirectory readFrom:file.
+
+        "/ set file position to start of central directory
+        (pos0 - (centralDirectory centralDirectorySize)) < startOfArchive ifTrue: [
+            ^ ZipFileFormatErrorSignal raiseRequestErrorString:' - central directory start is out of the archive bounds'.
+        ].
+
+        file position0Based:(pos0 - (centralDirectory centralDirectorySize)).
+
         "/ read central directory entries
-        0 to:(count_in-1) do:[:i |
+        1 to:(centralDirectory centralDirectoryTotalNoOfEntries) do:[:i |
             |zipd filename_length centralFileHeaderSignature relative_offset_local_header 
-             posOfNextMember extra crcBytes|
+             posOfNextMember extra|
 
             (file position + (self class centralDirectoryMinimumSize)) > endOfArchive ifTrue: [
                 ^ ZipFileFormatErrorSignal raiseRequestErrorString:' - central directory entry out of archive bounds'.
             ].
             centralFileHeaderSignature := file nextLongMSB:false.            
             centralFileHeaderSignature ~= C_CENTRALHEADERSIGNATURE ifTrue:[
-                self warn:'ZipArchive: file format error - bad centralHeaderSignature in:' ,
-                            (file isFileStream ifTrue:[file pathName] ifFalse:['inStream']).
+                ZipFileFormatErrorSignal raiseRequestErrorString:' - file format error - bad centralHeaderSignature in: ' ,
+                                                (file isFileStream ifTrue:[file pathName] ifFalse:['inStream']).
                 ^ self.
             ].
 
             zipd := ZipMember new.
-
-            zipd versionMadeBy:(file nextUnsignedShortMSB:false). 
-            zipd versionNeedToExtract:(file nextUnsignedShortMSB:false). 
-            zipd generalPurposBitFlag:(file nextUnsignedShortMSB:false). 
-            zipd compressionMethod:(file nextUnsignedShortMSB:false).
-            zipd lastModFileTime:(file nextUnsignedShortMSB:false).   
-            zipd lastModFileDate:(file nextUnsignedShortMSB:false).
-            "/ next long did not work because it could be in that case a signed small integer
-            crcBytes := ByteArray with:file next with:file next with:file next with:file next.
-            zipd crc32: (LargeInteger digitBytes: crcBytes MSB: false).
-            zipd compressedSize:(file nextLongMSB:false).     
-            zipd uncompressedSize:(file nextLongMSB:false).      
-            zipd fileNameLength:(file nextUnsignedShortMSB:false).   
-            zipd extraFieldLength:(file nextUnsignedShortMSB:false). 
-            zipd fileCommentLength:(file nextUnsignedShortMSB:false). 
-            zipd diskNumberStart:(file nextUnsignedShortMSB:false).  
-            zipd internalFileAttributes:(file nextUnsignedShortMSB:false).   
-            zipd externalFileAttributes:(file nextLongMSB:false).
-            zipd relativeLocalHeaderOffset:(file nextLongMSB:false).
-
-            filename_length := zipd fileNameLength.
-            (file position + filename_length) > endOfArchive ifTrue: [
-                ^ ZipFileFormatErrorSignal raiseRequestErrorString:' - central directory entry out of archive bounds'.
-            ].
-            "/ read file name
-            zipd fileName:(dataString := String new:filename_length).
-            file nextBytes:filename_length into:dataString.
-
-            zipd extraFieldLength ~~ 0 ifTrue: [
-                (file position + (zipd extraFieldLength)) > endOfArchive ifTrue: [
-                    ^ ZipFileFormatErrorSignal raiseRequestErrorString:' - central directory entry out of archive bounds'.
-                ].
-                "/ read extra field
-                zipd extraField:(dataString := String new:(zipd extraFieldLength)).
-                file nextBytes:(zipd extraFieldLength) into:dataString.
-            ].
-
-            zipd fileCommentLength ~~ 0 ifTrue: [
-                (file position + (zipd fileCommentLength)) > endOfArchive ifTrue: [
-                    ^ ZipFileFormatErrorSignal raiseRequestErrorString:' - central directory entry out of archive bounds'.
-                ].
-                "/ read file comment
-                zipd fileComment:(dataString := String new:(zipd fileCommentLength)).
-                file nextBytes:(zipd fileCommentLength) into:dataString.
-            ].
-
-            "/ central directory header read is now complete
-            "/ remember this file position (start of next member)
-"/            posOfNextMember := file position.
-    
-            "/ reposition in file to get start of data section
-"/            relative_offset_local_header := zipd relativeLocalHeaderOffset.
-"/            file position0Based:(relative_offset_local_header + 28).
-"/            extra := file nextUnsignedShortMSB:false.
-"/            zipd dataStart:(relative_offset_local_header + "C_SIZEOFLOCALHEADER" 30 + filename_length + extra ).
-
-            "/ reposition in file to next member
-"/            file position:posOfNextMember.
-
+            zipd readCentralDirectoryEntryFrom:file.
             self addMember:zipd.
         ].
 
         (file position + 6) > endOfArchive ifTrue: [
-            "/ archive have no digital signature
+            "/ archive has no digital signature
             ^ self.
         ].
 
         "/ check for digital signature
         ((file next ~~ ($P codePoint))
-        or:[file next ~~ ($K codePoint)
-        or:[file next ~~ 8r005
-        or:[file next ~~ 8r005]]]) ifTrue:[
-            centralDirectory digitalSignatureDataSize:(file nextUnsignedShortMSB:false).
-            centralDirectory digitalSignatureDataSize ~~ 0 ifTrue: [
-                (file position + (centralDirectory digitalSignatureDataSize)) > endOfArchive ifTrue: [
-                    ^ ZipFileFormatErrorSignal raiseRequestErrorString:' - digital signature entry out of archive bounds'.
-                ].
-                "/ read digital signature data
-                centralDirectory digitalSignatureData:(dataString := String new:(centralDirectory digitalSignatureDataSize)).
-                file nextBytes:(centralDirectory digitalSignatureDataSize) into:dataString.
-            ].
+         or:[file next ~~ ($K codePoint)
+         or:[file next ~~ 8r005
+         or:[file next ~~ 8r005]]]) ifTrue:[
+            centralDirectory readDigitalSignatureFrom:file.
         ].
     ]
 
@@ -3922,35 +3744,6 @@
     ^ true.
 !
 
-extractArchive:fileName
-    <resource: #obsolete>
-    "extract a filename entry as a byteArray;
-     nil on errors"
-
-    |zmemb|
-
-    (file isNil or: [mode ~~ #read]) ifTrue: [
-        ^ self error: 'Archiv not open for reading ...'.
-    ].    
-
-    zmemb := self findMember:fileName.
-    zmemb isNil ifTrue:[^ nil].
-    (zmemb fileStart + startOfArchive) > endOfArchive ifTrue: [
-        ^ ZipFileFormatErrorSignal raiseRequestErrorString:' - zipEntry start is out of the archive bounds'.
-    ].
-
-    (zmemb fileStart + (zmemb compressedSize)) > endOfArchive ifTrue: [
-        ^ ZipFileFormatErrorSignal raiseRequestErrorString:' - zipEntry end is out of the archive bounds'.
-    ].
-
-    "/ open archive and set bounds for the requested archive
-    "/ this can now be handled like an ordinary archive
-
-    ^ self class oldFileNamed:archiveName 
-               startOfArchive:(zmemb fileStart + startOfArchive) 
-                 endOfArchive:(zmemb fileStart + startOfArchive + (zmemb compressedSize)).
-!
-
 restoreOsDirectory:osDirectoryName fromArchiveDirectory: archiveDirectoryName
     |osDirectory directoryAlreadyCreated archiveDirectoryNameSize|
 
@@ -4012,7 +3805,31 @@
 
 readStreamFor:nameOfFileInArchive
     "open a stream on archive contents identified by nameOfFileInArchive"
-    self shouldImplement.
+
+    |zipEntry|
+
+    (file isNil or:[mode ~~ #read]) ifTrue:[
+        self error:'ZipArchive not open for reading ...'.
+        ^ nil
+    ].    
+
+    zipEntry := self findMember:nameOfFileInArchive.
+    zipEntry isNil ifTrue:[^ nil].
+
+    (zipEntry fileStart + startOfArchive) > endOfArchive ifTrue: [
+        ZipFileFormatErrorSignal raiseRequestErrorString:' - zipEntry start is out of the archive bounds'.
+        ^ nil
+    ].
+
+    (zipEntry fileStart + startOfArchive + (zipEntry compressedSize)) > endOfArchive ifTrue: [
+        ZipFileFormatErrorSignal raiseRequestErrorString:' - zipEntry end is out of the archive bounds'.
+        ^ nil
+    ].
+
+    file position0Based:(zipEntry fileStart + startOfArchive).
+
+    ^ (ZipReadStream zipFileStream:file zipEntry:zipEntry)
+        zipArchive:self.
 ! !
 
 !ZipArchive methodsFor:'testing'!
@@ -4059,14 +3876,15 @@
             fileNameOrDirectoryEntry readingFileDo: [:aStream|    
                 self addFile: (archiveDirectoryName, '/', entry) 
                      fromStream: aStream 
-                     compressMethod: theCompressMethod.
+                     compressMethod: theCompressMethod
+                     asDirectory:false.
             ].
         ].
     ].
 !
 
 addArchiveDirectoryCompressed: archiveDirectoryName fromOsDirectory: osDirectoryName
-    ^ self addArchiveDirectory: archiveDirectoryName fromOsDirectory: osDirectoryName compressMethod: COMPR_DEFLATED 
+    ^ self addArchiveDirectory: archiveDirectoryName fromOsDirectory: osDirectoryName compressMethod:COMPR_DEFLATED 
 !
 
 addDirectory: aDirectoryName
@@ -4074,24 +3892,25 @@
 
     <resource: #obsolete>
 
-    ^ self addFile: aDirectoryName withContents: nil compressMethod: 0 asDirectory: true.
+    ^ self addFile:aDirectoryName withContents:nil compressMethod:COMPR_STORED asDirectory:true.
 !
 
 addFile: aFileName fromStream: aStream
-    ^ self addFile: aFileName fromStream: aStream compressMethod: 0
+    ^ self addFile: aFileName fromStream: aStream compressMethod:COMPR_STORED asDirectory:false
+!
+
+addFile:aFileName fromStream:aStream compressMethod: theCompressMethodArg
+    ^ self addFile:aFileName fromStream:aStream compressMethod:theCompressMethodArg asDirectory:false
 !
 
-addFile: aFileName fromStream: aStream compressMethod: theCompressMethodArg
-    |zipEntry curTime curDate crc32Pos crc32 unCompressedDataSize
-      compressedDataSize buffer rdSize nextBlockSize streamBufferSize 
-      myZipStream startDataPosition theZipFileName theCompressMethod|
-
-    "/ sr & cg:
-    "/ please refactor by calling
-    "/    self addFile: aFileName fromStream: aStream compressMethod: theCompressMethod asDirectory:false
+addFile:aFileName fromStream:aStream compressMethod:theCompressMethodArg asDirectory:isDirectory
+    "do not create directories (isDirectory = true) - they are not compatible between operating systems"
+
+    |zipEntry curTime curDate theZipFileName theCompressMethod streamBufferSize buffer 
+     crc32 unCompressedDataSize startDataPosition nextBlockSize myZipStream|
 
     (file isNil or: [mode ~~ #write]) ifTrue: [
-        ^ self error: 'Archiv not open for writing ...'.
+        ^ self error: 'ZipArchive not open for writing ...'.
     ].
 
     theCompressMethod := theCompressMethodArg.
@@ -4104,14 +3923,7 @@
     ].
 
     zipEntry := ZipMember new default.
-
-    firstEntry isNil ifTrue: [
-        firstEntry := zipEntry.
-    ] ifFalse: [
-        lastEntry next: zipEntry.
-    ].
-
-    lastEntry := zipEntry.
+    self addMember:zipEntry.
 
     theZipFileName := self validZipFileNameFrom:aFileName. 
 
@@ -4119,9 +3931,14 @@
     zipEntry fileNameLength: theZipFileName size.
     zipEntry uncompressedSize: 0.
 
-    zipEntry compressionMethod: theCompressMethod.
-    zipEntry internalFileAttributes: 1.
-    zipEntry externalFileAttributes: EXTERNALFILEATTRIBUTES_ISFILE.
+    isDirectory ifTrue: [
+        theCompressMethod := COMPR_STORED.
+        zipEntry externalFileAttributes: EXTERNALFILEATTRIBUTES_ISDIRECTORY.
+    ] ifFalse: [
+        zipEntry compressionMethod: theCompressMethod.
+        zipEntry internalFileAttributes: 1.
+        zipEntry externalFileAttributes: EXTERNALFILEATTRIBUTES_ISFILE.
+    ].
 
     curTime := Time now.
     curDate := Date today.
@@ -4132,59 +3949,32 @@
     "/ ensure that the file position is at the end
     file setToEnd.
 
-    zipEntry relativeLocalHeaderOffset:(file position).
-    file nextPutLong: 16r04034b50  MSB:false.
-    file nextPutShort:zipEntry versionNeedToExtract MSB:false.
-    file nextPutShort:zipEntry generalPurposBitFlag MSB:false.
-    file nextPutShort:zipEntry compressionMethod MSB:false.
-    file nextPutShort:zipEntry lastModFileTime MSB:false.
-    file nextPutShort:zipEntry lastModFileDate MSB:false.
-    crc32Pos := file position.
-    file nextPutLong:zipEntry crc32 MSB:false.
-    file nextPutLong:zipEntry compressedSize MSB:false.
-    file nextPutLong:zipEntry uncompressedSize MSB:false.
-    file nextPutShort:zipEntry fileNameLength MSB:false.
-    file nextPutShort:zipEntry extraFieldLength MSB:false.
-    file nextPutAll:zipEntry fileName.
-    zipEntry extraField notNil ifTrue: [
-        file nextPutAll:zipEntry extraField.
-    ].
-
+    zipEntry writeTo:file.
+
+    streamBufferSize := self class streamBufferSize.    
+    buffer := ByteArray new:streamBufferSize.
     crc32 := 0.
-    streamBufferSize := self class streamBufferSize.    
-    buffer := ByteArray new: streamBufferSize.
-    rdSize := aStream size.
-    unCompressedDataSize := rdSize.
-    compressedDataSize   := 0.
-    startDataPosition := file position.
+    unCompressedDataSize := 0.
+    startDataPosition := file position0Based.
 
     [
-        [rdSize > 0] whileTrue: [
-            rdSize > (self class streamBufferSize) ifTrue: [
-                nextBlockSize := streamBufferSize.
-            ] ifFalse: [
-                (nextBlockSize := rdSize) > 0 ifTrue:[
-                    buffer := ByteArray new: nextBlockSize.
-                ].
-            ].
+        [aStream atEnd] whileFalse: [
+            nextBlockSize := aStream nextBytes:streamBufferSize into:buffer startingAt:1.
 
             nextBlockSize > 0 ifTrue: [
-                aStream nextBytes:nextBlockSize into:buffer startingAt:1.
-                crc32 := (ZipStream crc32BytesIn: buffer crc: crc32).
-                (theCompressMethod == COMPR_DEFLATED) ifTrue: [
+                unCompressedDataSize := unCompressedDataSize + nextBlockSize.
+                crc32 := ZipStream crc32BytesIn: buffer from:1 to:nextBlockSize crc:crc32.
+                theCompressMethod == COMPR_DEFLATED ifTrue: [
                     myZipStream isNil ifTrue: [
-                        myZipStream := ZipStream writeOpenAsZipStreamOn: file.
+                        myZipStream := ZipStream writeOpenAsZipStreamOn:file.
                     ].
                     myZipStream nextPutBytes:nextBlockSize from:buffer startingAt:1.
-                ] ifFalse: [
-                    (theCompressMethod == COMPR_STORED) ifTrue: [
-                        file nextPutBytes:nextBlockSize from:buffer startingAt:1.
-                    ] ifFalse:[
-                        self error "/ cannot happen
-                    ]
-                ].
+                ] ifFalse: [theCompressMethod == COMPR_STORED ifTrue: [
+                    file nextPutBytes:nextBlockSize from:buffer startingAt:1.
+                ] ifFalse:[
+                    UnsupportedZipFileFormatErrorSignal raiseRequestErrorString:'unsupported compressMethod'.
+                ]].
             ].
-            rdSize := rdSize - nextBlockSize.
         ].
     ] ensure:[
         myZipStream notNil ifTrue:[
@@ -4192,50 +3982,39 @@
         ].
     ].
 
-    zipEntry compressedSize: (file position) - startDataPosition.
-
-    zipEntry crc32: crc32.
+    zipEntry compressedSize:(file position0Based) - startDataPosition.
+
+    "/ crc32 is allways reqired (not as written in docu to be zero in case of uncompressed mode)
+    zipEntry crc32:crc32.
     zipEntry uncompressedSize: unCompressedDataSize.
 
-    file position0Based:crc32Pos.
-
-    file nextPutLong:zipEntry crc32 MSB:false.
-    file nextPutLong:zipEntry compressedSize MSB:false.
-    file nextPutLong:zipEntry uncompressedSize MSB:false.
-
+    zipEntry rewriteCrcAndSizeTo:file.
     file setToEnd.
 !
 
 addFile: aFileName withContents: data
-    ^ self addFile: aFileName withContents: data compressMethod: 0 asDirectory: false.
+    ^ self addFile: aFileName withContents: data compressMethod:COMPR_STORED asDirectory: false.
 !
 
-addFile: aFileName withContents: data compressMethod: theCompressMethodArg asDirectory: isDirectory
+addFile:aFileName withContents:data compressMethod:theCompressMethodArg asDirectory:isDirectory
     "do not create directories (isDirectory = true) - they are not compatible between operating systems"
 
     |zipEntry theCompressedData curTime curDate theZipFileName theCompressMethod|
 
     (file isNil or: [mode ~~ #write]) ifTrue: [
-        ^ self error: 'Archiv not open for writing ...'.
+        ^ self error: 'ZipArchive not open for writing ...'.
     ].
 
     theCompressMethod := theCompressMethodArg.
     ((theCompressMethod == COMPR_DEFLATED) 
-    or:[ theCompressMethod == COMPR_STORED ]) ifFalse:[
+     or:[ theCompressMethod == COMPR_STORED ]) ifFalse:[
         UnsupportedZipFileFormatErrorSignal raiseRequestErrorString:'unsupported compressMethod'.
         "/ if proceeded, write as uncompressed
         theCompressMethod := COMPR_STORED
     ].
 
     zipEntry := ZipMember new default.
-
-    firstEntry isNil ifTrue: [
-        firstEntry := zipEntry.
-    ] ifFalse: [
-        lastEntry next: zipEntry.
-    ].
-
-    lastEntry := zipEntry.
+    self addMember:zipEntry.
 
     theZipFileName := self validZipFileNameFrom:aFileName. 
 
@@ -4281,22 +4060,7 @@
     "/ ensure that the file position is at the end
     file setToEnd.
 
-    zipEntry relativeLocalHeaderOffset:(file position).
-    file nextPutLong: 16r04034b50  MSB:false.
-    file nextPutShort:zipEntry versionNeedToExtract MSB:false.
-    file nextPutShort:zipEntry generalPurposBitFlag MSB:false.
-    file nextPutShort:zipEntry compressionMethod MSB:false.
-    file nextPutShort:zipEntry lastModFileTime MSB:false.
-    file nextPutShort:zipEntry lastModFileDate MSB:false.
-    file nextPutLong:zipEntry crc32 MSB:false.
-    file nextPutLong:zipEntry compressedSize MSB:false.
-    file nextPutLong:zipEntry uncompressedSize MSB:false.
-    file nextPutShort:zipEntry fileNameLength MSB:false.
-    file nextPutShort:zipEntry extraFieldLength MSB:false.
-    file nextPutAll:zipEntry fileName.
-    zipEntry extraField notNil ifTrue: [
-        file nextPutAll:zipEntry extraField.
-    ].
+    zipEntry writeTo:file.
 
     theCompressedData notNil ifTrue: [
         file nextPutBytes: zipEntry compressedSize from: theCompressedData.
@@ -4304,7 +4068,7 @@
 !
 
 addFileCompressed: aFileName fromStream: aStream
-    ^ self addFile: aFileName fromStream: aStream compressMethod: COMPR_DEFLATED
+    ^ self addFile: aFileName fromStream: aStream compressMethod: COMPR_DEFLATED asDirectory:false
 !
 
 addFileCompressed: aFileName withContents: data
@@ -4313,9 +4077,84 @@
 
 !ZipArchive methodsFor:'writing - stream'!
 
-writeStreamFor:nameOfFileInArchive
+compressedWriteStreamFor:nameOfFileInArchive
+    "create new entry in central directory"
+
+    ^ self writeStreamFor:nameOfFileInArchive compressMethod:COMPR_DEFLATED
+!
+
+writeStreamFor:nameOfFileInArchive compressMethod:theCompressMethodArg
     "create new entry in central directory"
-    self shouldImplement.
+
+    |zipEntry curTime curDate theZipFileName theCompressMethod|
+
+    (file isNil or: [mode ~~ #write]) ifTrue: [
+        ^ self error: 'ZipArchive not open for writing ...'.
+    ].
+
+    theCompressMethod := theCompressMethodArg.
+
+    ((theCompressMethod == COMPR_DEFLATED) 
+    or:[ theCompressMethod == COMPR_STORED ]) ifFalse:[
+        UnsupportedZipFileFormatErrorSignal raiseRequestErrorString:'unsupported compressMethod'.
+        "/ if proceeded, write as uncompressed
+        theCompressMethod := COMPR_STORED
+    ].
+
+    zipEntry := ZipMember new default.
+    self addMember:zipEntry.
+
+    theZipFileName := self validZipFileNameFrom:nameOfFileInArchive. 
+
+    zipEntry fileName: theZipFileName.
+    zipEntry fileNameLength: theZipFileName size.
+    zipEntry uncompressedSize: 0.
+
+    zipEntry compressionMethod: theCompressMethod.
+    zipEntry internalFileAttributes: 1.
+    zipEntry externalFileAttributes: EXTERNALFILEATTRIBUTES_ISFILE.
+
+    curTime := Time now.
+    curDate := Date today.
+    "/ data and time in msdos format
+    zipEntry lastModFileTime: (((curTime seconds // 2) bitOr: (curTime minutes rightShift: -5)) bitOr: (curTime hours rightShift: -11)).
+    zipEntry lastModFileDate: (((curDate day) bitOr: (curDate month rightShift: -5)) bitOr: (((curDate year) - 1980) rightShift: -9)).
+
+    "/ ensure that the file position is at the end
+    file setToEnd.
+
+    zipEntry writeTo:file.
+
+    ^ (ZipWriteStream zipFileStream:file zipEntry:zipEntry)
+        zipArchive:self.
+! !
+
+!ZipArchive::AbstractZipStream class methodsFor:'instance creation'!
+
+zipFileStream:something zipEntry:compressionMethodArg
+    ^ self basicNew zipFileStream:something zipEntry:compressionMethodArg
+! !
+
+!ZipArchive::AbstractZipStream methodsFor:'accessing'!
+
+zipArchive
+    ^ zipArchive
+!
+
+zipArchive:something
+    zipArchive := something.
+!
+
+zipEntry
+    ^ zipEntry
+!
+
+zipEntry:something
+    zipEntry := something.
+!
+
+zipFileStream
+    ^ zipFileStream
 ! !
 
 !ZipArchive::ZipCentralDirectory methodsFor:'accessing'!
@@ -4415,6 +4254,37 @@
     digitalSignatureData := nil.
 ! !
 
+!ZipArchive::ZipCentralDirectory methodsFor:'reading & writing'!
+
+readDigitalSignatureFrom:aStream
+    "read a digitalSignature trailer from aStream"
+
+    digitalSignatureDataSize := aStream nextUnsignedShortMSB:false.
+    digitalSignatureDataSize ~~ 0 ifTrue:[
+"/        (file position + (centralDirectory digitalSignatureDataSize)) > endOfArchive ifTrue: [
+"/            ^ ZipFileFormatErrorSignal raiseRequestErrorString:' - digital signature entry out of archive bounds'.
+"/        ].
+        digitalSignatureData := String new:digitalSignatureDataSize.
+        aStream nextBytes:digitalSignatureDataSize into:digitalSignatureData.
+    ].
+!
+
+readFrom:aStream
+    "read a Central Directory Header from aStream"
+
+    numberOfThisDisk := aStream nextUnsignedShortMSB:false.
+    centralDirectoryStartDiskNumber := aStream nextUnsignedShortMSB:false.
+    centralDirectoryTotalNoOfEntriesOnThisDisk := aStream nextUnsignedShortMSB:false.
+    centralDirectoryTotalNoOfEntries := aStream nextUnsignedShortMSB:false.
+    centralDirectorySize := aStream nextLongMSB:false.
+    centralDirectoryStartOffset := aStream nextLongMSB:false.
+    zipCommentLength := aStream nextUnsignedShortMSB:false.
+    zipCommentLength ~~ 0 ifTrue: [
+        zipComment := String new:zipCommentLength.
+        aStream nextBytes:zipCommentLength into:zipComment.
+    ].
+! !
+
 !ZipArchive::ZipMember class methodsFor:'documentation'!
 
 documentation
@@ -4476,8 +4346,7 @@
 !
 
 dataStart
-    "return the value of the instance variable 'dataStart' (automatically generated)"
-
+    "tell the file offset, where tha data of this zip entry starts"
     dataStart isNil ifTrue: [
         dataStart := relativeLocalHeaderOffset 
                     + "C_SIZEOFLOCALHEADER" 30 
@@ -4684,10 +4553,269 @@
     "Created: / 29.3.1998 / 19:10:57 / cg"
 ! !
 
+!ZipArchive::ZipMember methodsFor:'reading & writing'!
+
+readCentralDirectoryEntryFrom:aStream
+    "read a central directory entry"
+
+    versionMadeBy := aStream nextUnsignedShortMSB:false. 
+    versionNeedToExtract := aStream nextUnsignedShortMSB:false. 
+    generalPurposBitFlag := aStream nextUnsignedShortMSB:false. 
+    compressionMethod := aStream nextUnsignedShortMSB:false.
+    lastModFileTime := aStream nextUnsignedShortMSB:false.   
+    lastModFileDate := aStream nextUnsignedShortMSB:false.
+    crc32 := aStream nextUnsignedLongMSB: false.
+    compressedSize := aStream nextLongMSB:false.     
+    uncompressedSize := aStream nextLongMSB:false.      
+    fileNameLength := aStream nextUnsignedShortMSB:false.   
+    extraFieldLength := aStream nextUnsignedShortMSB:false. 
+    fileCommentLength := aStream nextUnsignedShortMSB:false. 
+    diskNumberStart := aStream nextUnsignedShortMSB:false.  
+    internalFileAttributes := aStream nextUnsignedShortMSB:false.   
+    externalFileAttributes := aStream nextLongMSB:false.
+    relativeLocalHeaderOffset := aStream nextLongMSB:false.
+
+"/    (aStream position + fileNameLength) > endOfArchive ifTrue: [
+"/        ^ ZipArchive zipFileFormatErrorSignal raiseRequestErrorString:' - central directory entry out of archive bounds'.
+"/    ].
+    fileName:= String new:fileNameLength.
+    aStream nextBytes:fileNameLength into:fileName.
+
+    extraFieldLength ~~ 0 ifTrue: [
+"/        (aStream position + extraFieldLength) > endOfArchive ifTrue: [
+"/            ^ ZipArchive zipFileFormatErrorSignal raiseRequestErrorString:' - central directory entry out of archive bounds'.
+"/        ].
+        extraField := String new:extraFieldLength.
+        aStream nextBytes:extraFieldLength into:extraField.
+    ].
+
+    fileCommentLength ~~ 0 ifTrue: [
+"/        (aStream position + fileCommentLength) > endOfArchive ifTrue: [
+"/            ^ ZipArchive zipFileFormatErrorSignal raiseRequestErrorString:' - central directory entry out of archive bounds'.
+"/        ].
+        fileComment := String new:fileCommentLength.
+        aStream nextBytes:fileCommentLength into:fileComment.
+    ].
+!
+
+rewriteCrcAndSizeTo:aStream
+    "Header has already been written - now rewrite CRC and sizes"
+
+    aStream position:relativeLocalHeaderOffset+14.
+
+    aStream 
+        nextPutLong:crc32 MSB:false;
+        nextPutLong:compressedSize MSB:false;
+        nextPutLong:uncompressedSize MSB:false.
+!
+
+writeTo:aStream
+    "represent myself on aStream"
+
+    relativeLocalHeaderOffset := aStream position.
+
+    aStream 
+        nextPutLong:16r04034b50  MSB:false;
+        nextPutShort:versionNeedToExtract MSB:false;
+        nextPutShort:generalPurposBitFlag MSB:false;
+        nextPutShort:compressionMethod MSB:false;
+        nextPutShort:lastModFileTime MSB:false;
+        nextPutShort:lastModFileDate MSB:false;
+        nextPutLong:crc32 MSB:false;
+        nextPutLong:compressedSize MSB:false;
+        nextPutLong:uncompressedSize MSB:false;
+        nextPutShort:fileNameLength MSB:false;
+        nextPutShort:extraFieldLength MSB:false;
+        nextPutAll:fileName.
+
+    extraField notNil ifTrue: [
+        aStream nextPutAll:extraField.
+    ].
+! !
+
+!ZipArchive::ZipReadStream methodsFor:'closing'!
+
+close
+    "nothing to do here"
+! !
+
+!ZipArchive::ZipReadStream methodsFor:'initialization'!
+
+zipFileStream:something  zipEntry:aZipEntry
+
+    zipEntry := aZipEntry.
+    zipFileStream := something.
+    startDataPosition := zipFileStream position0Based.
+    crc32 := 0.
+    uncompressedDataSize := zipEntry uncompressedSize.
+    readPosition := 0.
+
+    zipEntry compressionMethod == ZipArchive COMPR_DEFLATED ifTrue:[
+        compressingStream := ZipStream readOpenAsZipStreamOn:zipFileStream.
+    ] ifFalse:[
+        compressingStream := zipFileStream.
+    ].
+! !
+
+!ZipArchive::ZipReadStream methodsFor:'queries'!
+
+atEnd
+    ^ peek isNil and:[readPosition >= uncompressedDataSize]
+!
+
+position
+    ^ readPosition
+! !
+
+!ZipArchive::ZipReadStream methodsFor:'reading'!
+
+next
+    "read a character"
+
+    |result|
+
+    peek notNil ifTrue:[
+        result := peek.
+        peek := nil.
+    ] ifFalse:[
+        readPosition >= uncompressedDataSize ifTrue:[
+            ^ self pastEndRead.        
+        ].
+
+        result := compressingStream next.
+    ].
+
+    readPosition := readPosition + 1.
+    ^ result.
+!
+
+peek
+    "peek a character"
+
+    peek notNil ifTrue:[
+        ^ peek.
+    ].
+
+    readPosition >= uncompressedDataSize ifTrue:[
+        ^ self pastEndRead.        
+    ].
+
+    peek := compressingStream next.
+    ^ peek.
+! !
+
+!ZipArchive::ZipWriteStream methodsFor:'closing'!
+
+close
+    "finalize the data"
+
+    compressingStream ~~ zipFileStream ifTrue:[
+        "close ZipStream"
+        compressingStream close.
+    ].
+    compressingStream := nil.
+
+    zipEntry compressedSize:(zipFileStream position0Based) - startDataPosition.
+
+    "/ crc32 is allways reqired (not as written in docu to be zero in case of uncompressed mode)
+    zipEntry crc32:crc32.
+    zipEntry uncompressedSize:uncompressedDataSize.
+
+    zipEntry rewriteCrcAndSizeTo:zipFileStream.
+
+    zipFileStream setToEnd.
+! !
+
+!ZipArchive::ZipWriteStream methodsFor:'initialization'!
+
+zipFileStream:something  zipEntry:aZipEntry
+
+    zipEntry := aZipEntry.
+    zipFileStream := something.
+    startDataPosition := zipFileStream position0Based.
+    crc32 := 0.
+    uncompressedDataSize := 0.
+
+    zipEntry compressionMethod ==  ZipArchive COMPR_DEFLATED ifTrue:[
+        compressingStream := ZipStream writeOpenAsZipStreamOn:zipFileStream.
+    ] ifFalse:[
+        compressingStream := zipFileStream.
+    ].
+! !
+
+!ZipArchive::ZipWriteStream methodsFor:'queries'!
+
+isReadable
+    "return true, if reading is supported by the recevier.
+     This has to be redefined in concrete subclasses."
+
+    ^ false
+!
+
+isWritable
+    "return true, if writing is supported by the recevier.
+     This has to be redefined in concrete subclasses."
+
+    ^ true
+! !
+
+!ZipArchive::ZipWriteStream methodsFor:'reading'!
+
+contents
+    "return the entire contents of the stream.
+     For a readStream, that is the rest (i.e. upToEnd),
+     for a writeStream, that is the collected data. As we do not know here,
+     what we are, this is the responsibility of a subclass..."
+
+    self shouldNotImplement
+!
+
+next
+    "return the next element of the stream
+     - we do not know here how to do it, it must be redefined in subclass"
+
+    self shouldNotImplement
+! !
+
+!ZipArchive::ZipWriteStream methodsFor:'writing'!
+
+contents:aCollection
+    |size|
+
+    size := aCollection size.
+    uncompressedDataSize := uncompressedDataSize + size.
+    crc32 := ZipStream crc32BytesIn:aCollection from:1 to:size crc:crc32.
+    compressingStream contents:aCollection
+!
+
+flush
+    compressingStream flush
+!
+
+nextPut:anObject
+    "put the argument, anObject onto the receiver
+     - we do not know here how to do it, it must be redefined in subclass"
+
+    uncompressedDataSize := uncompressedDataSize + 1.
+    crc32 := ZipStream crc32Add:anObject crc:crc32.
+    compressingStream nextPut:anObject
+!
+
+nextPutAll:aCollection
+    |size|
+
+    size := aCollection size.
+    size = 0 ifFalse:[
+        uncompressedDataSize := uncompressedDataSize + size.
+        crc32 := ZipStream crc32BytesIn:aCollection from:1 to:size crc:crc32.
+        compressingStream nextPutAll:aCollection
+    ].
+! !
+
 !ZipArchive class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic2/ZipArchive.st,v 1.75 2009-06-23 20:38:56 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic2/ZipArchive.st,v 1.76 2009-06-30 15:32:14 stefan Exp $'
 ! !
 
 ZipArchive initialize!