ZipArchive.st
changeset 1994 76336287ae17
parent 1993 64e0530befa6
child 1995 93f2f08bceb3
--- a/ZipArchive.st	Tue May 27 18:15:53 2008 +0200
+++ b/ZipArchive.st	Wed May 28 18:20:00 2008 +0200
@@ -12,7 +12,8 @@
 "{ Package: 'stx:libbasic2' }"
 
 Object subclass:#ZipArchive
-	instanceVariableNames:'file mode archiveName firstEntry lastEntry centralDirectory'
+	instanceVariableNames:'file mode archiveName firstEntry lastEntry centralDirectory
+		startOfArchive endOfArchive'
 	classVariableNames:'Lobby RecentlyUsedZipArchives FlushBlock ECREC_SIZE LREC_SIZE
 		CREC_SIZE SIZE_CENTRAL_DIRECTORY TOTAL_ENTRIES_CENTRAL_DIR
 		C_COMPRESSED_SIZE C_RELATIVE_OFFSET_LOCAL_HEADER
@@ -1151,6 +1152,7 @@
     zipwr closeFile.
                                                         [exEnd]
 
+                                                        [exBegin]
     |zipwr ziprd testDirectory testFileWr testFileRd zs|
 
     testDirectory := 'C:\Dokumente und Einstellungen\stefan\Eigene Dateien\tmp\'.
@@ -1166,7 +1168,9 @@
     zs := ziprd readStreamFor: 'crcTest_resume_compressed.txt'.
     zs inspect.
     ziprd close.
-
+                                                        [exEnd]
+
+                                                        [exBegin]
     |zipwr ziprd testDirectory testFileWr testFileRd rs result|
 
     testDirectory := 'C:\Dokumente und Einstellungen\stefan\Eigene Dateien\tmp\'.
@@ -1187,6 +1191,59 @@
     result inspect.
     rs close.
     ziprd close.
+                                                        [exEnd]
+
+    read an archive with files and/or directories and/or zipArchives, 
+    fetch the entries (also from the include zip archives) 
+    and create a new archive
+                                                        [exBegin]
+    |ziprd zipwr entryDict testDirectory testFileRd testFileWr zipRdSub1 zipRdSub2|
+
+    testDirectory := 'C:\Dokumente und Einstellungen\stefan\Eigene Dateien\tmp\'.
+    testFileRd := 'ZipInZipFileTest.zip'.
+    testFileWr := 'ZipInZipFileTest_generated.zip'.
+
+    ziprd := ZipArchive oldFileNamed:(testDirectory, testFileRd).
+    entryDict := Dictionary new.
+    ziprd entries do: [:aFileName|
+        Transcript showCR: 'processing in top: ', aFileName.
+        (aFileName endsWith:'.zip') ifTrue: [
+            zipRdSub1 := ziprd extractArchive: aFileName.
+            zipRdSub1 entries do: [:aFileName1|
+                Transcript showCR: 'processing in sub 1: ', aFileName1.
+                (aFileName1 endsWith:'.zip') ifTrue: [
+                    zipRdSub2 := zipRdSub1 extractArchive: aFileName1.
+                    zipRdSub2 entries do: [:aFileName2|
+                        Transcript showCR: 'processing in sub 2: ', aFileName2.
+                        (aFileName2 endsWith:'.zip') ifTrue: [
+                            self halt.
+                        ] ifFalse: [
+                            entryDict at:aFileName2 put:(zipRdSub2 extract: aFileName2) asString.
+                        ].
+                    ].
+                    zipRdSub2 closeFile.
+                ] ifFalse: [
+                    entryDict at:aFileName1 put:(zipRdSub1 extract: aFileName1) asString.
+                ].
+            ].
+            zipRdSub1 closeFile.
+        ] ifFalse: [
+            entryDict at:aFileName put:(ziprd extract: aFileName) asString.
+        ].
+    ].
+    ziprd closeFile.
+
+    zipwr := ZipArchive newFileNamed:(testDirectory, testFileWr).
+    entryDict keysAndValuesDo: [:key :value|
+        (value size == 0) ifTrue: [
+            zipwr addDirectory:key.
+        ] ifFalse: [
+            zipwr addFile:key withContents:value
+        ].
+    ].
+    zipwr closeFile.
+                                                        [exEnd]
+
 "
 !
 
@@ -2724,6 +2781,19 @@
 
     "Created: / 29.3.1998 / 17:46:09 / cg"
     "Modified: / 20.10.1998 / 00:30:02 / cg"
+!
+
+oldFileNamed:name startOfArchive: startOfArchive endOfArchive: endOfArchive
+    |zar f fn|
+
+    f := name asFilename.
+    f exists ifFalse:[^ nil].
+
+    fn := f pathName.
+    zar := self new.
+    zar setArchiveStartPosition: startOfArchive endPosition: endOfArchive.
+    zar name:fn mode:#read.
+    ^ zar
 ! !
 
 !ZipArchive class methodsFor:'Signal constants'!
@@ -2826,6 +2896,12 @@
     ^ LREC_SIZE
 
     "Created: / 29.3.1998 / 19:11:20 / cg"
+!
+
+centralDirectoryMinimumSize
+    ^ 46
+
+    "Created: / 29.3.1998 / 19:11:20 / cg"
 ! !
 
 !ZipArchive class methodsFor:'debugging'!
@@ -2872,6 +2948,11 @@
     "return the (file-)name of this zipArchive"
 
     ^ archiveName
+!
+
+setArchiveStartPosition: aStartposition endPosition: anEndPosition
+    startOfArchive := aStartposition.
+    endOfArchive   := anEndPosition.
 ! !
 
 !ZipArchive methodsFor:'finalization'!
@@ -3069,6 +3150,23 @@
 
         Lobby register:self.
     ].
+!
+
+setDefaultArchiveBounds
+    " set start and end of archive if it is nil. That means no bounds was defined
+      before. In that case the archive is the complete file.
+    "
+    startOfArchive isNil ifTrue: [
+        "/ set archive zero position
+        file reset.
+        startOfArchive := file position.
+    ].
+
+    endOfArchive isNil ifTrue: [
+        "/ set archive end position
+        file setToEnd.
+        endOfArchive   := file position.
+    ].
 ! !
 
 !ZipArchive methodsFor:'private-decompression'!
@@ -3255,13 +3353,15 @@
 checkZipArchive
     "read the zip directory into a linked-list of zipMembers"
 
-    |size count_in foundPK pos0|
+    |size count_in|
 
     file isNil ifTrue: [
         ^ false
     ].
 
-    size := file fileSize.
+    self setDefaultArchiveBounds.
+
+    size := endOfArchive - startOfArchive.
     (size == 0) ifTrue:[
         count_in := 0.
         ^ false
@@ -3271,33 +3371,7 @@
         ^ false.
     ].
 
-    foundPK := false.
-    file position0Based:(pos0 := size - ECREC_SIZE - 4).
-
-    "/ set position to end of central directory record
-    ((file next ~~ ($P codePoint))
-    or:[file next ~~ ($K codePoint)
-    or:[file next ~~ 8r005
-    or:[file next ~~ 8r006]]]) ifTrue:[
-        "/ search for end of central directory signature, this is 
-        "/ necessary if the archive includes a .ZIP file comment
-        file reset. "/ (pos0 - 100).
-        [file atEnd not and:[foundPK not]] whileTrue:[
-            (file next == ($P codePoint)
-            and:[file next == ($K codePoint)
-            and:[file next == 8r005
-            and:[file next == 8r006]]]) ifTrue:[
-                foundPK := true.
-                pos0 := file position0Based - 4.
-            ]
-        ].
-        foundPK ifTrue:[
-            'ZipArchive includes a .ZIP file comment; resynchronized' infoPrintCR.
-        ] ifFalse:[
-            ^ false.
-        ]
-    ].
-    ^ true
+    ^ self searchForEndOfCentralDirectorySignature
 !
 
 findMember:name
@@ -3314,9 +3388,12 @@
 readDirectory
     "read the zip directory into a linked-list of zipMembers"
 
-    |size count_in foundPK pos0 dataString|
-
-    size := file fileSize.
+    |size count_in pos0 dataString|
+
+    self setDefaultArchiveBounds.
+
+"/    size := file fileSize.
+    size := endOfArchive - startOfArchive.
     (size == 0) ifTrue:[
         count_in := 0.
         ^ self
@@ -3326,33 +3403,13 @@
         ^ ZipFileFormatErrorSignal raiseRequestErrorString:' - zipfile too short'.
     ].
 
-    foundPK := false.
-    file position0Based:(pos0 := size - ECREC_SIZE - 4).
-
-    "/ set position to end of central directory record
-    ((file next ~~ ($P codePoint))
-    or:[file next ~~ ($K codePoint)
-    or:[file next ~~ 8r005
-    or:[file next ~~ 8r006]]]) ifTrue:[
-        "/ search for end of central directory signature, this is 
-        "/ necessary if the archive includes a .ZIP file comment
-        file reset. "/ (pos0 - 100).
-        [file atEnd not and:[foundPK not]] whileTrue:[
-            (file next == ($P codePoint)
-            and:[file next == ($K codePoint)
-            and:[file next == 8r005
-            and:[file next == 8r006]]]) ifTrue:[
-                foundPK := true.
-                pos0 := file position0Based - 4.
-            ]
-        ].
-        foundPK ifTrue:[
-            'ZipArchive includes a .ZIP file comment; resynchronized' infoPrintCR.
-        ] ifFalse:[
-            ^ ZipFileFormatErrorSignal raiseRequestErrorString:' - invalid zipfile'.
-        ]
+    self searchForEndOfCentralDirectorySignature ifFalse: [
+        ^ ZipFileFormatErrorSignal raiseRequestErrorString:' - could not find end of directory signature'.
     ].
 
+    "/ position before end of central directory signature
+    pos0 := file position0Based - 4.
+
     "/ Now we have found the end of central directory record
     centralDirectory := ZipCentralDirectory new.
     centralDirectory numberOfThisDisk:(file nextUnsignedShortMSB:false).
@@ -3369,8 +3426,11 @@
     ].
 
     "/ 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|
@@ -3383,6 +3443,9 @@
             |zipd filename_length centralFileHeaderSignature relative_offset_local_header 
              posOfNextMember extra crcBytes|
 
+            (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:' ,
@@ -3412,17 +3475,26 @@
             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.
@@ -3444,6 +3516,11 @@
             self addMember:zipd.
         ].
 
+        (file position + 6) > endOfArchive ifTrue: [
+            "/ archive have no digital signature
+            ^ self.
+        ].
+
         "/ check for digital signature
         ((file next ~~ ($P codePoint))
         or:[file next ~~ ($K codePoint)
@@ -3451,6 +3528,9 @@
         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.
@@ -3467,6 +3547,51 @@
     "Modified: / 19.10.1998 / 21:27:32 / cg"
 !
 
+searchForEndOfCentralDirectorySignature
+    "read the zip directory into a linked-list of zipMembers"
+
+    |size foundPK pos0 searchEndPos|
+
+    foundPK := false.
+    size := endOfArchive - startOfArchive.
+    file position0Based:(pos0 := size - ECREC_SIZE - 4).
+
+    "/ set position to end of central directory record
+    ((file next ~~ ($P codePoint))
+    or:[file next ~~ ($K codePoint)
+    or:[file next ~~ 8r005
+    or:[file next ~~ 8r006]]]) ifTrue:[
+        "/ search from end of archive backwards for "end of central directory signature", 
+        "/ this is necessary if the archive includes a .ZIP file comment or a digital signature
+        "/ then the end of the directory signature may be on an other position
+
+        "/ but the "end of central directory signature" must be located in the 
+        "/ last 64k of the archive
+        size > 65536 ifTrue: [
+            searchEndPos := (endOfArchive - 65536).
+        ] ifFalse: [
+            searchEndPos := startOfArchive.
+        ].
+
+        file position0Based: (pos0 := endOfArchive - 4).
+
+        [foundPK] whileFalse: [
+            (file next == ($P codePoint)
+            and:[file next == ($K codePoint)
+            and:[file next == 8r005
+            and:[file next == 8r006]]]) ifTrue:[
+                ^ true                
+            ].
+            file position <= searchEndPos ifTrue: [
+                ^ false.
+            ].
+            file position0Based: (pos0 := pos0 - 1).
+        ].
+        ^ false
+    ].
+    ^ true
+!
+
 zipMembersDo:aBlock
     "evaluate aBlock for all zipMembers"
 
@@ -3496,8 +3621,15 @@
 
     zmemb := self findMember:fileName.
     zmemb isNil ifTrue:[^ nil].
-
-    file position0Based:(zmemb fileStart).
+    (zmemb fileStart + startOfArchive) > endOfArchive ifTrue: [
+        ^ ZipFileFormatErrorSignal raiseRequestErrorString:' - zipEntry start is out of the archive bounds'.
+    ].
+
+    (zmemb fileStart + startOfArchive + (zmemb compressedSize)) > endOfArchive ifTrue: [
+        ^ ZipFileFormatErrorSignal raiseRequestErrorString:' - zipEntry end is out of the archive bounds'.
+    ].
+
+    file position0Based:(zmemb fileStart + startOfArchive).
     rawContents := file nextBytes:(zmemb compressedSize).
 
     data := self
@@ -3508,6 +3640,33 @@
     ^ data.
 !
 
+extractArchive:fileName
+    "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 ordenary archive
+
+    ^ self class oldFileNamed:archiveName 
+               startOfArchive:(zmemb fileStart + startOfArchive) 
+                 endOfArchive:(zmemb fileStart + startOfArchive + (zmemb compressedSize)).
+!
+
 readStreamFor:nameOfFileInArchive
     "open a stream on archive contents identified by nameOfFileInArchive"
 
@@ -4106,7 +4265,7 @@
 !ZipArchive class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic2/ZipArchive.st,v 1.61 2008-05-27 16:15:53 ab Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic2/ZipArchive.st,v 1.62 2008-05-28 16:20:00 ab Exp $'
 ! !
 
 ZipArchive initialize!