*** empty log message ***
authorab
Tue, 27 May 2008 18:15:53 +0200
changeset 1993 64e0530befa6
parent 1992 be159b5be71f
child 1994 76336287ae17
*** empty log message ***
ZipArchive.st
--- a/ZipArchive.st	Thu May 15 15:32:05 2008 +0200
+++ b/ZipArchive.st	Tue May 27 18:15:53 2008 +0200
@@ -36,6 +36,13 @@
 	privateIn:ZipArchive
 !
 
+ZipStream subclass:#ZipCompressedArchiveStream
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:ZipArchive
+!
+
 Object subclass:#ZipMember
 	instanceVariableNames:'next versionMadeBy versionNeedToExtract generalPurposBitFlag
 		compressionMethod lastModFileTime lastModFileDate crc32
@@ -48,6 +55,13 @@
 	privateIn:ZipArchive
 !
 
+FileStream subclass:#ZipUncompressedArchiveStream
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:ZipArchive
+!
+
 !ZipArchive primitiveDefinitions!
 %{
 
@@ -1055,7 +1069,7 @@
                                                         [exEnd]
 
 
-    compatibility check with winzip (compressed with deflate)
+    compatibility write check with winzip (compressed with deflate)
                                                         [exBegin]
     |zipwr testDirectory testFileWr|
 
@@ -1067,7 +1081,20 @@
     zipwr closeFile.
                                                         [exEnd]
 
-    compatibility check with winzip (uncompressed)
+    compatibility read check with winzip (compressed with deflate)
+                                                        [exBegin]
+    |ziprd testDirectory testFileRd contents|
+
+    testDirectory := 'C:\Dokumente und Einstellungen\stefan\Eigene Dateien\tmp\'.
+    testFileRd := 'crcTest_resume_compressed.zip'.
+
+    ziprd := ZipArchive oldFileNamed:(testDirectory, testFileRd).
+    contents := ziprd extract: ziprd entries first.
+    contents inspect.
+    ziprd closeFile.
+                                                        [exEnd]
+
+    compatibility write check with winzip (uncompressed)
                                                         [exBegin]
     |zipwr testDirectory testFileWr|
 
@@ -1084,6 +1111,19 @@
     zipwr closeFile.
                                                         [exEnd]
 
+    compatibility read check with winzip (uncompressed)
+                                                        [exBegin]
+    |ziprd testDirectory testFileRd contents|
+
+    testDirectory := 'C:\Dokumente und Einstellungen\stefan\Eigene Dateien\tmp\'.
+    testFileRd := 'crcTest_resume_uncompressed.zip'.
+
+    ziprd := ZipArchive oldFileNamed:(testDirectory, testFileRd).
+    contents := ziprd extract: ziprd entries first.
+    contents inspect.
+    ziprd closeFile.
+                                                        [exEnd]
+
     read an archive with files and/or directories, fetch the entries 
     and create a new archive with the same content
                                                         [exBegin]
@@ -1111,6 +1151,42 @@
     zipwr closeFile.
                                                         [exEnd]
 
+    |zipwr ziprd testDirectory testFileWr testFileRd zs|
+
+    testDirectory := 'C:\Dokumente und Einstellungen\stefan\Eigene Dateien\tmp\'.
+    testFileWr := 'crcTest_resume_compressed.zip'.
+
+    zipwr := ZipArchive newFileNamed:(testDirectory, testFileWr).
+    zipwr addFile:'crcTest_resume_compressed.txt' withContents: 'Das ist ein test, das ist ein test, das ist ein test'.
+    zipwr close.
+
+    testFileRd := 'crcTest_resume_compressed.zip'.
+
+    ziprd := ZipArchive oldFileNamed:(testDirectory, testFileRd).
+    zs := ziprd readStreamFor: 'crcTest_resume_compressed.txt'.
+    zs inspect.
+    ziprd close.
+
+    |zipwr ziprd testDirectory testFileWr testFileRd rs result|
+
+    testDirectory := 'C:\Dokumente und Einstellungen\stefan\Eigene Dateien\tmp\'.
+    testFileWr := 'readStreamTest_HelloWorld.zip'.
+
+    zipwr := ZipArchive newFileNamed:(testDirectory, testFileWr).
+    zipwr addFile:'readStreamTest_HelloWorld.txt' withContents: 'Hello World!!' compressed: false.
+    zipwr close.
+
+    testFileRd := 'readStreamTest_HelloWorld.zip'.
+    ziprd := ZipArchive oldFileNamed:(testDirectory, testFileRd).
+    rs := ziprd readStreamFor: 'readStreamTest_HelloWorld.txt'.
+
+    result := ''.
+    [ rs atEnd ] whileFalse: [
+        result := result, (rs nextAvailable:5).
+    ].
+    result inspect.
+    rs close.
+    ziprd close.
 "
 !
 
@@ -2844,6 +2920,112 @@
 
 !ZipArchive methodsFor:'private'!
 
+addContentsToArchiveFrom: realFileName to: zipFileName compress: aCompressFlag
+    |fromStream zipEntry data archiveData curTime curDate theCompressMethod positionSize|
+    aCompressFlag ifTrue: [
+        fromStream := realFileName readStream.
+        theCompressMethod := 8.
+    ] ifFalse: [
+        fromStream := realFileName readStream.
+        theCompressMethod := 0.
+    ].
+
+    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.
+
+    zipEntry fileName: zipFileName.
+    zipEntry fileNameLength: zipFileName size.
+    zipEntry uncompressedSize: 0.
+
+    zipEntry compressionMethod: theCompressMethod.
+    zipEntry internalFileAttributes: 1.
+    zipEntry externalFileAttributes: 32.
+
+    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 == 8) 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
+    doCompressFlag ifFalse: [
+        ^ self addFile: aFileName withContents: data compressMethod: 0 asDirectory: false.
+    ].
+    ^ self addFile: aFileName withContents: data compressMethod: 8 asDirectory: false.
+!
+
 checkZipArchive:archiveFileName
     |isValidArchive|
 
@@ -3324,10 +3506,61 @@
                 size:(zmemb uncompressedSize).
 
     ^ data.
+!
+
+readStreamFor:nameOfFileInArchive
+    "open a stream on archive contents identified by nameOfFileInArchive"
+
+    |zmemb rs zs|
+
+    (file isNil or: [mode ~~ #read]) ifTrue: [
+        ^ self error: 'Archiv not open for reading ...'.
+    ].    
+
+    zmemb := self findMember:nameOfFileInArchive.
+    zmemb isNil ifTrue:[^ nil].
+
+    zmemb compressionMethod == 0 ifTrue: [
+        rs := ZipUncompressedArchiveStream readonlyFileNamed: archiveName asFilename.
+        rs position0Based:zmemb fileStart.
+        rs readLimit:(zmemb fileStart + zmemb uncompressedSize).
+        ^ rs
+    ].
+
+    zs := ZipCompressedArchiveStream readOpenOn:rs 
+                                       position:zmemb fileStart 
+                                      readLimit:zmemb compressedSize.
+    ^ zs
+!
+
+restoreContentsFromZipDirectory:zipDirectoryName intoDirectory:intoDirectory
+    "restore the contents of a file or directory (recursive) from zip archive -> zipDirectoryName 
+     into directory -> intoDirectory"
+    intoDirectory exists ifFalse: [
+        ^ false
+    ].
+    ^ true
 ! !
 
 !ZipArchive methodsFor:'writing'!
 
+addContentsFromFileOrDirectory:realFileOrDirectoryName toZipDirectory:zipDirectoryName
+    "add the contents of a file or directory (recursive) -> realFileOrDirectoryName 
+     to the zip archive into the zip archive directory -> zipDirectoryName"
+    |zipFileName|
+    realFileOrDirectoryName exists ifFalse: [
+        ^ false
+    ].
+
+    self addDirectory: zipDirectoryName.
+
+    realFileOrDirectoryName isDirectory ifFalse: [
+        zipFileName := zipDirectoryName, '/', realFileOrDirectoryName baseName.
+        ^ self addContentsToArchiveFrom: realFileOrDirectoryName to: zipFileName compress: false.
+    ].
+    ^ true
+!
+
 addDirectory: aDirectoryName
     ^ self addFile: aDirectoryName withContents: nil compressMethod: 0 asDirectory: true.
 !
@@ -3342,7 +3575,6 @@
     (file isNil or: [mode ~~ #write]) ifTrue: [
         ^ self error: 'Archiv not open for writing ...'.
     ].
-
     zipEntry := ZipMember new default.
 
     firstEntry isNil ifTrue: [
@@ -3407,6 +3639,7 @@
     zipEntry extraField notNil ifTrue: [
         file nextPutAll:zipEntry extraField.
     ].
+
     theCompressedData notNil ifTrue: [
         file nextPutBytes: zipEntry compressedSize from: theCompressedData.
     ].
@@ -3471,7 +3704,7 @@
 !
 
 numberOfThisDisk
-    ^ numberOfThisDisk
+    ^ numberOfThisDisk.
 !
 
 numberOfThisDisk:something
@@ -3509,6 +3742,87 @@
     digitalSignatureData := nil.
 ! !
 
+!ZipArchive::ZipCompressedArchiveStream class methodsFor:'instance creation'!
+
+readOpenOn:aStream position: atPosition readLimit: aReadLimit
+    "open to read data from an compressed stream"
+
+    ^ self basicNew openWithMode:#readonly on:aStream position: atPosition readlimit: aReadLimit
+! !
+
+!ZipArchive::ZipCompressedArchiveStream methodsFor:'accessing'!
+
+position: something
+    position := something
+!
+
+readLimit: something
+    readLimit := something
+! !
+
+!ZipArchive::ZipCompressedArchiveStream methodsFor:'startup & release'!
+
+openWithMode:aMode on:aStream position: atPosition readlimit: aReadlimit
+    "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
+    "
+    |flags|
+    aStream isNil ifTrue:[
+        ^ self errorNotOpen
+    ].
+
+    onStream    := aStream.    
+    mode        := aMode.
+    outputBytes := ExternalBytes unprotectedNew:16384.
+    inputBytes  := ExternalBytes unprotectedNew:16384.
+    readLimit   := aReadlimit.
+    position    := atPosition.
+    binary      := false.
+
+    self zopen.
+    self registerForFinalization.
+
+    hitEOF := false.
+
+    aMode == #readonly ifTrue:[
+        self zinflateInit.
+    ] ifFalse:[
+        self zdeflateInit
+    ].
+
+    onStream position0Based: atPosition.
+    onStream readLimit: aReadlimit.
+    self halt.
+    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'
+    ].
+
+    "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_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.
+    ].
+! !
+
 !ZipArchive::ZipMember class methodsFor:'documentation'!
 
 documentation
@@ -3778,10 +4092,21 @@
     "Created: / 29.3.1998 / 19:10:57 / cg"
 ! !
 
+!ZipArchive::ZipUncompressedArchiveStream methodsFor:'non homogenous reading'!
+
+nextAvailable:count
+    |end|
+    end := position + count.
+    (end - ZeroPosition + 1) > readLimit ifTrue:[
+        end := readLimit.
+    ].
+    ^ super nextAvailable: end - position.
+! !
+
 !ZipArchive class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic2/ZipArchive.st,v 1.60 2008-05-06 13:18:48 ca Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic2/ZipArchive.st,v 1.61 2008-05-27 16:15:53 ab Exp $'
 ! !
 
 ZipArchive initialize!