ZipArchive.st
changeset 4335 d39f2d7d91b1
parent 4283 1491d5c3783a
child 4372 071c7186de7b
--- a/ZipArchive.st	Fri Feb 17 11:08:34 2017 +0100
+++ b/ZipArchive.st	Sat Feb 18 00:26:06 2017 +0100
@@ -14,7 +14,7 @@
 "{ NameSpace: Smalltalk }"
 
 Object subclass:#ZipArchive
-	instanceVariableNames:'file mode archiveName firstEntry lastEntry centralDirectory
+	instanceVariableNames:'stream mode archiveName firstEntry lastEntry centralDirectory
 		startOfArchive endOfArchive zipMembersByName appendTrailingSlash'
 	classVariableNames:'RecentlyUsedZipArchives FlushBlock ZipFileFormatErrorSignal
 		UnsupportedZipFileFormatErrorSignal DefaultAppendTrailingSlash
@@ -2928,7 +2928,10 @@
 oldFileNamed:name startOfArchive: startOfArchive endOfArchive: endOfArchive
     ^ self new
         setArchiveStartPosition:startOfArchive endPosition:endOfArchive;
-        name:name mode:#read.
+        name:name mode:#read;
+        yourself.
+
+    "Modified: / 17-02-2017 / 22:15:25 / stefan"
 !
 
 readingFrom:aPositionableStream
@@ -3191,12 +3194,13 @@
 !
 
 file
-    ^ file
+    <resource: #obsolete>
+    ^ stream
 !
 
 fileSize
-    file notNil ifTrue:[
-        ^ file size
+    stream notNil ifTrue:[
+        ^ stream size
     ].
     ^ 0
 !
@@ -3231,6 +3235,12 @@
     ^ archiveName
 !
 
+rawStream
+    ^ stream
+
+    "Created: / 17-02-2017 / 23:13:54 / stefan"
+!
+
 setArchiveStartPosition: aStartposition endPosition: anEndPosition
     startOfArchive := aStartposition.
     endOfArchive   := anEndPosition.
@@ -3243,13 +3253,71 @@
 !
 
 size
-    ^self fileSize
+    ^ self fileSize
+
+    "Modified (format): / 17-02-2017 / 22:30:50 / stefan"
 !
 
 zipMembersByName
     ^ zipMembersByName
 ! !
 
+!ZipArchive methodsFor:'comparing'!
+
+= aZipArchiveToCompare
+    "open both archives
+        - check file size
+        - check number of archive members
+        - perform a binary compare of the archives."
+
+    |streamBufferSize rdSize buf1 buf2 nextBlockSize stream1 stream2|
+
+    self == aZipArchiveToCompare ifTrue:[
+        ^ true.
+    ].
+    self class ~~ aZipArchiveToCompare class ifTrue:[
+        ^ false.
+    ].
+    (self fileSize ~= aZipArchiveToCompare fileSize) ifTrue:[
+        ^ false
+    ].
+    (self numberOfEntries ~= aZipArchiveToCompare numberOfEntries) ifTrue:[
+        ^ false
+    ].
+
+    "/ perform a binary compare of the archives
+    streamBufferSize := self class streamBufferSize.    
+    rdSize           := self fileSize.
+    buf1             := ByteArray new:streamBufferSize.
+    buf2             := ByteArray new:streamBufferSize.
+    stream1          := self rawStream.
+    stream2          := aZipArchiveToCompare rawStream.
+
+    stream1 reset.
+    stream2 reset.
+
+    [rdSize > 0] whileTrue:[
+        rdSize > streamBufferSize ifTrue: [
+            nextBlockSize := streamBufferSize.
+        ] ifFalse: [
+            nextBlockSize := rdSize.
+            buf1 := ByteArray new:nextBlockSize.
+            buf2 := ByteArray new:nextBlockSize.
+        ].
+
+        stream1 nextBytes:nextBlockSize into:buf1 startingAt:1.
+        stream2 nextBytes:nextBlockSize into:buf2 startingAt:1.
+        buf1 ~= buf2 ifTrue:[    
+            ^ false.
+        ].
+        rdSize := rdSize - nextBlockSize.
+    ].
+
+    ^ true
+
+    "Created: / 17-02-2017 / 23:22:11 / stefan"
+! !
+
 !ZipArchive methodsFor:'error raising'!
 
 error:anErrorString
@@ -3261,10 +3329,10 @@
 !ZipArchive methodsFor:'open & close'!
 
 close
-    file notNil ifTrue:[
+    stream notNil ifTrue:[
         self flush.
-        file close.
-        file := archiveName := centralDirectory := zipMembersByName := nil.
+        stream close.
+        stream := archiveName := centralDirectory := zipMembersByName := nil.
         firstEntry := lastEntry := nil.
     ].
 !
@@ -3272,7 +3340,7 @@
 flush
     "finish the zip archive, but do not close the underlying stream"
 
-    (file notNil and:[mode == #write]) ifTrue: [
+    (stream notNil and:[mode == #write]) ifTrue: [
         self addCentralZipDirectory
     ]
 !
@@ -3290,7 +3358,7 @@
         ^ OpenError raiseRequestWith:filename errorString:' - file is a directory'.
     ].
 
-    file notNil ifTrue: [
+    stream notNil ifTrue: [
         self close.
     ].
 
@@ -3301,8 +3369,8 @@
     mode ~~ #write ifTrue:[
         |mustCloseFile|
 
+        mustCloseFile := true.
         [
-            mustCloseFile := true.
             self readDirectory.
             mustCloseFile := false.
 
@@ -3313,7 +3381,7 @@
                 maxStartPosition := members maxApplying:[:eachMember | self dataStartOf:eachMember].
                 lastMember := members detect:[:eachMember | eachMember dataStart = maxStartPosition].
 
-                file position:(startOfArchive + lastMember dataStart + lastMember compressedSize).
+                stream position:(startOfArchive + lastMember dataStart + lastMember compressedSize).
                 mode := #write.
             ].
         ] ensure:[
@@ -3324,6 +3392,7 @@
     ].
 
     "Modified: / 31-08-2010 / 12:39:25 / sr"
+    "Modified: / 17-02-2017 / 22:13:02 / stefan"
 !
 
 readFrom:aPositionableStream
@@ -3338,15 +3407,15 @@
 readingFrom:aPositionableStream
     "initialize the archive to read from aPositionableStream"
 
-    file notNil ifTrue: [
-        file ~~ aPositionableStream ifTrue: [
+    stream notNil ifTrue: [
+        stream ~~ aPositionableStream ifTrue: [
             self close.
         ].
     ].
 
     mode := #read.
     aPositionableStream binary.
-    file := aPositionableStream.
+    stream := aPositionableStream.
     aPositionableStream isFileStream ifTrue:[
         archiveName := aPositionableStream pathName.
         aPositionableStream isDirectory ifTrue:[
@@ -3361,10 +3430,10 @@
 !
 
 reopenForReading
-    file isNil ifTrue:[
+    stream isNil ifTrue:[
         mode := #read.
-        file := archiveName asFilename readStream.
-        file binary
+        stream := archiveName asFilename readStream.
+        stream binary
     ]
 
     "Created: / 21-11-2010 / 12:02:37 / cg"
@@ -3373,13 +3442,13 @@
 writingTo:aPositionableStream
     "initialize the archive to write to aPositionableStream"
 
-    file notNil ifTrue: [
+    stream notNil ifTrue: [
         self close.
     ].
 
     mode := #write.
     aPositionableStream binary.
-    file := aPositionableStream.
+    stream := aPositionableStream.
     aPositionableStream isFileStream ifTrue:[
         archiveName := aPositionableStream pathName.
     ] ifFalse:[
@@ -3436,9 +3505,9 @@
            the central directory entry!!
     "
 
-    file position:fileHeaderStart+26.
-    fileNameLength := file nextUnsignedInt16MSB:false.
-    extraFieldLength := file nextUnsignedInt16MSB:false.
+    stream position:fileHeaderStart+26.
+    fileNameLength := stream nextUnsignedInt16MSB:false.
+    extraFieldLength := stream nextUnsignedInt16MSB:false.
 
     dataStart := fileHeaderStart + 30 + fileNameLength + extraFieldLength.
 
@@ -3453,18 +3522,18 @@
 openFile
     |fn|
 
-    file isNil ifTrue:[
+    stream isNil ifTrue:[
         fn := archiveName asFilename.
         mode ~~ #write ifTrue:[
             mode == #append ifTrue:[
-                file := fn readWriteStream.
+                stream := fn readWriteStream.
             ] ifFalse:[
-                file := fn readStream.
+                stream := fn readStream.
             ].
         ] ifFalse:[
-            file := fn writeStream
+            stream := fn writeStream
         ].
-        file binary.
+        stream binary.
     ].
 
     "Modified: / 31-08-2010 / 12:40:41 / sr"
@@ -3481,34 +3550,21 @@
 
     endOfArchive isNil ifTrue: [
         "/ set archive end position
-        endOfArchive := file size.
+        endOfArchive := stream size.
     ].
 !
 
 validZipFileNameFrom:zipFileName
-    |fileNameParts partCol partOfPartCol validZipFileName theElement|
-    fileNameParts := OrderedCollection new.
-
-    partCol := zipFileName asCollectionOfSubstringsSeparatedBy:$\.
-    partCol do:[:aSegm|
-        partOfPartCol := aSegm asCollectionOfSubstringsSeparatedBy:$/.
-        partOfPartCol do:[:nextSegm|
-            fileNameParts add: nextSegm.
-        ].
-    ].
-
-    fileNameParts do:[:anElement|
-        anElement notEmptyOrNil ifTrue:[    
-            theElement := anElement.
-"/ disabled by sr - no reason to not allow spaces in a fileName
-"/            (anElement includes:$ ) ifTrue:[ 
-"/                theElement := (anElement replString:' ' withString:'').
-"/            ].
-
+    |fileNameParts validZipFileName|
+
+    fileNameParts := zipFileName asCollectionOfSubstringsSeparatedByAny:'/\'.
+
+    fileNameParts do:[:eachPart|
+        eachPart notEmptyOrNil ifTrue:[    
             validZipFileName isNil ifTrue:[
-                validZipFileName := theElement.
+                validZipFileName := eachPart.
             ] ifFalse:[
-                validZipFileName := (validZipFileName, '/', theElement).
+                validZipFileName := validZipFileName, '/', eachPart.
             ].
         ].
     ].
@@ -3526,6 +3582,8 @@
     ZipArchive new validZipFileNameFrom:'hello/\world'
     ZipArchive new validZipFileNameFrom:'hello/\world/aaa bbb/ccc'
 "
+
+    "Modified (format): / 17-02-2017 / 22:30:11 / stefan"
 ! !
 
 !ZipArchive methodsFor:'private - decompression'!
@@ -3663,61 +3721,61 @@
     noEntries := 0.
 
     "/ ensure that the file position is at end
-    file setToEnd.
-
-    centralDirectory centralDirectoryStartOffset: file position.
+    stream setToEnd.
+
+    centralDirectory centralDirectoryStartOffset: stream position.
 
     self zipMembersDo:[:zipEntry |
         noEntries := noEntries + 1.
-        file nextPutInt32LSB: C_CENTRAL_HEADER_SIGNATURE.            
-        file nextPutInt16LSB:zipEntry versionMadeBy.
-        file nextPutInt16LSB:zipEntry versionNeedToExtract.
-        file nextPutInt16LSB:zipEntry generalPurposBitFlag.
-        file nextPutInt16LSB:zipEntry compressionMethod.
-        file nextPutInt16LSB:zipEntry lastModFileTime.
-        file nextPutInt16LSB:zipEntry lastModFileDate.
-        file nextPutInt32LSB:zipEntry crc32.
-        file nextPutInt32LSB:zipEntry compressedSize.
-        file nextPutInt32LSB:zipEntry uncompressedSize.
-        file nextPutInt16LSB:zipEntry fileNameLength.
-        file nextPutInt16LSB:zipEntry extraFieldLength.
-        file nextPutInt16LSB:zipEntry fileCommentLength.
-        file nextPutInt16LSB:zipEntry diskNumberStart.
-        file nextPutInt16LSB:zipEntry internalFileAttributes.
-        file nextPutInt32LSB:zipEntry externalFileAttributes.
-        file nextPutInt32LSB:zipEntry relativeLocalHeaderOffset.
+        stream nextPutInt32LSB: C_CENTRAL_HEADER_SIGNATURE.            
+        stream nextPutInt16LSB:zipEntry versionMadeBy.
+        stream nextPutInt16LSB:zipEntry versionNeedToExtract.
+        stream nextPutInt16LSB:zipEntry generalPurposBitFlag.
+        stream nextPutInt16LSB:zipEntry compressionMethod.
+        stream nextPutInt16LSB:zipEntry lastModFileTime.
+        stream nextPutInt16LSB:zipEntry lastModFileDate.
+        stream nextPutInt32LSB:zipEntry crc32.
+        stream nextPutInt32LSB:zipEntry compressedSize.
+        stream nextPutInt32LSB:zipEntry uncompressedSize.
+        stream nextPutInt16LSB:zipEntry fileNameLength.
+        stream nextPutInt16LSB:zipEntry extraFieldLength.
+        stream nextPutInt16LSB:zipEntry fileCommentLength.
+        stream nextPutInt16LSB:zipEntry diskNumberStart.
+        stream nextPutInt16LSB:zipEntry internalFileAttributes.
+        stream nextPutInt32LSB:zipEntry externalFileAttributes.
+        stream nextPutInt32LSB:zipEntry relativeLocalHeaderOffset.
 
         self assert:zipEntry fileNameLength = zipEntry fileName size.
-        file nextPutAll:zipEntry fileName.
+        stream nextPutAll:zipEntry fileName.
 
         zipEntry extraField notNil ifTrue: [
             self assert:zipEntry extraFieldLength = zipEntry extraField size.
-            file nextPutAll:zipEntry extraField.
+            stream nextPutAll:zipEntry extraField.
         ].
         zipEntry fileComment notNil ifTrue: [
             self assert:zipEntry fileCommentLength = zipEntry fileComment size.
-            file nextPutAll:zipEntry fileComment.
+            stream nextPutAll:zipEntry fileComment.
         ].
     ].
 
     centralDirectory centralDirectoryTotalNoOfEntries: noEntries.
     centralDirectory centralDirectoryTotalNoOfEntriesOnThisDisk: noEntries.
-    centralDirectory centralDirectorySize: (file position) - (centralDirectory centralDirectoryStartOffset).
-
-    file nextPutByte:($P codePoint).
-    file nextPutByte:($K codePoint).
-    file nextPutByte:8r005.
-    file nextPutByte:8r006.
-    file nextPutInt16LSB:centralDirectory numberOfThisDisk.
-    file nextPutInt16LSB:centralDirectory centralDirectoryStartDiskNumber.
-    file nextPutInt16LSB:centralDirectory centralDirectoryTotalNoOfEntriesOnThisDisk.
-    file nextPutInt16LSB:centralDirectory centralDirectoryTotalNoOfEntries.
-    file nextPutInt32LSB:centralDirectory centralDirectorySize.
-    file nextPutInt32LSB:centralDirectory centralDirectoryStartOffset.
-    file nextPutInt16LSB:centralDirectory zipCommentLength.
+    centralDirectory centralDirectorySize: (stream position) - (centralDirectory centralDirectoryStartOffset).
+
+    stream nextPutByte:($P codePoint).
+    stream nextPutByte:($K codePoint).
+    stream nextPutByte:8r005.
+    stream nextPutByte:8r006.
+    stream nextPutInt16LSB:centralDirectory numberOfThisDisk.
+    stream nextPutInt16LSB:centralDirectory centralDirectoryStartDiskNumber.
+    stream nextPutInt16LSB:centralDirectory centralDirectoryTotalNoOfEntriesOnThisDisk.
+    stream nextPutInt16LSB:centralDirectory centralDirectoryTotalNoOfEntries.
+    stream nextPutInt32LSB:centralDirectory centralDirectorySize.
+    stream nextPutInt32LSB:centralDirectory centralDirectoryStartOffset.
+    stream nextPutInt16LSB:centralDirectory zipCommentLength.
 
     centralDirectory zipCommentLength ~~ 0 ifTrue: [
-        file nextPutAll: centralDirectory zipComment.
+        stream nextPutAll: centralDirectory zipComment.
     ].
 
     "Modified: / 19-11-2010 / 16:23:36 / cg"
@@ -3726,40 +3784,41 @@
 addMember:zmemb
     "add a zipMember"
 
-    (firstEntry isNil) ifTrue:[
+    zipMembersByName at:zmemb fileName put:zmemb ifPresent:[:oldEntry| 
+            "ignore duplicate entries for backward compatibility.
+             Argh: expecco once added wrong duplicates to the end of ets files.
+                   The first entry is valid."
+            Logger warning:'duplicate entry in ZIP file ignored: %1' with:zmemb fileName.
+            ^ oldEntry.
+        ].
+
+    firstEntry isNil ifTrue:[
         firstEntry := zmemb
     ] ifFalse:[
         lastEntry next:zmemb.
     ].
     lastEntry := zmemb.
-    (zipMembersByName includesKey:zmemb fileName) ifTrue:[
-        "ignore duplicate entries for backward compatibility.
-         Argh: expecco once added wrong duplicates to the end of ets files.
-               The first entry is valid."
-        Logger warning:'duplicate entry in ZIP file ignored: %1' with:zmemb fileName.
-    ] ifFalse:[
-        zipMembersByName at:zmemb fileName put:zmemb.
-    ].
+
     ^ zmemb.
 
-    "Modified: / 30.3.1998 / 17:13:20 / cg"
-    "Created: / 9.9.1998 / 20:33:06 / cg"
+    "Modified: / 30-03-1998 / 17:13:20 / cg"
+    "Created: / 09-09-1998 / 20:33:06 / cg"
+    "Modified: / 17-02-2017 / 23:47:28 / stefan"
 !
 
 checkZipArchive
     "check if my file is really a zip archive. answer true or false."
 
-    |size count_in|
-
-    file isNil ifTrue: [
+    |size|
+
+    stream isNil ifTrue: [
         ^ false
     ].
 
     self setDefaultArchiveBounds.
 
     size := endOfArchive - startOfArchive.
-    (size == 0) ifTrue:[
-        count_in := 0.
+    size == 0 ifTrue:[
         ^ false
     ].
 
@@ -3768,22 +3827,22 @@
     ].
 
     ^ self searchForEndOfCentralDirectorySignature
+
+    "Modified (format): / 17-02-2017 / 22:21:09 / stefan"
 !
 
 checkZipArchive:archiveFileName
-    |isValidArchive|
-
     archiveName := archiveFileName asFilename name.
-    isValidArchive := false.
     mode := #read.
     self openFile.
 
-    [
-        isValidArchive := self checkZipArchive.
+    ^ [
+        self checkZipArchive.
     ] ensure:[
         self close.
     ].
-    ^ isValidArchive
+
+    "Modified: / 17-02-2017 / 22:22:44 / stefan"
 !
 
 findMember:name
@@ -3819,11 +3878,11 @@
     "Created: / 20-07-2012 / 19:33:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
-findMemberForWhich:aBlock
+findMemberForWhich:aOneArgBlock
     "find a zipMember by condition"
 
     self zipMembersDo:[:zipd |
-        (aBlock value:zipd) ifTrue:[^ zipd].
+        (aOneArgBlock value:zipd) ifTrue:[^ zipd].
     ].
     ^ nil
 
@@ -3851,16 +3910,16 @@
     ].
 
     "/ position before end of central directory signature
-    pos0 := file position - 4.
+    pos0 := stream position - 4.
 
     "/ Now we have found the end of central directory record
     centralDirectory := ZipCentralDirectory new.
     EndOfStreamNotification handle:[:ex|
         ZipFileFormatErrorSignal raiseRequestErrorString:' - file format error or short file: ' ,
-                                        (file isFileStream ifTrue:[file pathName] ifFalse:['inStream']).
+                                        (stream isFileStream ifTrue:[stream pathName] ifFalse:['inStream']).
         ^ self.
     ] do:[
-        centralDirectory readFrom:file.
+        centralDirectory readFrom:stream.
 
         "/ set file position to start of central directory
         (pos0 - centralDirectory centralDirectoryStartOffset - centralDirectory centralDirectorySize) < startOfArchive ifTrue: [
@@ -3868,40 +3927,39 @@
         ].
 
         startOfArchive := pos0 - centralDirectory centralDirectoryStartOffset - centralDirectory centralDirectorySize.
-        file position:(pos0 - (centralDirectory centralDirectorySize)).
+        stream position:(pos0 - (centralDirectory centralDirectorySize)).
 
         zipMembersByName := Dictionary new:centralDirectory centralDirectoryTotalNoOfEntries.
 
         "/ read central directory entries
         1 to:(centralDirectory centralDirectoryTotalNoOfEntries) do:[:i |
-            |zipd filename_length centralFileHeaderSignature relative_offset_local_header 
-             posOfNextMember extra|
-
-            (file position + (self class centralDirectoryMinimumSize)) > endOfArchive ifTrue: [
+            |zipd  centralFileHeaderSignature|
+
+            (stream position + (self class centralDirectoryMinimumSize)) > endOfArchive ifTrue: [
                 ^ ZipFileFormatErrorSignal raiseRequestErrorString:' - central directory entry out of archive bounds'.
             ].
-            centralFileHeaderSignature := file nextInt32MSB:false.            
+            centralFileHeaderSignature := stream nextInt32MSB:false.            
             centralFileHeaderSignature ~= C_CENTRAL_HEADER_SIGNATURE ifTrue:[
                 ZipFileFormatErrorSignal raiseRequestErrorString:' - file format error - bad centralHeaderSignature in: ' ,
-                                                (file isFileStream ifTrue:[file pathName] ifFalse:['inStream']).
+                                                (stream isFileStream ifTrue:[stream pathName] ifFalse:['inStream']).
                 ^ self.
             ].
 
-            zipd := ZipMember new readCentralDirectoryEntryFrom:file.
+            zipd := ZipMember new readCentralDirectoryEntryFrom:stream.
             self addMember:zipd.
         ].
 
-        (file position + 6) > endOfArchive ifTrue: [
+        (stream position + 6) > endOfArchive ifTrue: [
             "/ archive has no digital signature
             ^ self.
         ].
 
         "/ check for digital signature
-        ((file nextByte ~~ ($P codePoint))
-         or:[file nextByte ~~ ($K codePoint)
-         or:[file nextByte ~~ 8r005
-         or:[file nextByte ~~ 8r005]]]) ifTrue:[
-            centralDirectory readDigitalSignatureFrom:file.
+        ((stream nextByte ~~ ($P codePoint))
+         or:[stream nextByte ~~ ($K codePoint)
+         or:[stream nextByte ~~ 8r005
+         or:[stream nextByte ~~ 8r005]]]) ifTrue:[
+            centralDirectory readDigitalSignatureFrom:stream.
         ].
     ]
 
@@ -3912,6 +3970,7 @@
     "
 
     "Modified: / 19-11-2010 / 15:43:24 / cg"
+    "Modified (format): / 17-02-2017 / 22:20:26 / stefan"
 !
 
 searchForEndOfCentralDirectorySignature
@@ -3921,13 +3980,13 @@
 
     foundPK := false.
     size := endOfArchive - startOfArchive.
-    file position:(pos0 := endOfArchive - ECREC_SIZE - 4).
+    stream position:(pos0 := endOfArchive - ECREC_SIZE - 4).
 
     "/ set position to end of central directory record
-    ((file nextByte ~~ ($P codePoint))
-    or:[file nextByte ~~ ($K codePoint)
-    or:[file nextByte ~~ 8r005
-    or:[file nextByte ~~ 8r006]]]) ifTrue:[
+    ((stream nextByte ~~ ($P codePoint))
+    or:[stream nextByte ~~ ($K codePoint)
+    or:[stream nextByte ~~ 8r005
+    or:[stream nextByte ~~ 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
@@ -3940,22 +3999,22 @@
             searchEndPos := startOfArchive.
         ].
 
-        file position: (pos0 := endOfArchive - 4).
+        stream position: (pos0 := endOfArchive - 4).
 
         [foundPK] whileFalse: [
-            (file nextByte == ($P codePoint)
-            and:[file nextByte == ($K codePoint)
-            and:[file nextByte == 8r005
-            and:[file nextByte == 8r006]]]) ifTrue:[
+            (stream nextByte == ($P codePoint)
+            and:[stream nextByte == ($K codePoint)
+            and:[stream nextByte == 8r005
+            and:[stream nextByte == 8r006]]]) ifTrue:[
                 ^ true                
             ].
-            file position <= searchEndPos ifTrue: [
+            stream position <= searchEndPos ifTrue: [
                 ^ false.
             ].
             pos0 == 0 ifTrue:[
                 ^ false.
             ].
-            file position: (pos0 := pos0 - 1).
+            stream position: (pos0 := pos0 - 1).
         ].
         ^ false
     ].
@@ -3979,6 +4038,14 @@
 
 !ZipArchive methodsFor:'queries'!
 
+isValidFile: path
+    "Return true, if the recevier contains given file. false otherwise."
+
+    ^ zipMembersByName notNil and:[zipMembersByName includesKey:path]
+
+    "Created: / 20-05-2013 / 23:37:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 isValidPath: anArchivePathName
     self zipMembersByName
         keysDo:[:eachMemberName |
@@ -4007,8 +4074,8 @@
         do:[:zmemb :position |
             |rawContents data|
 
-            file position:position.
-            rawContents := file nextBytes:(zmemb compressedSize).
+            stream position:position.
+            rawContents := stream nextBytes:(zmemb compressedSize).
 
             data := self
                 decode:rawContents
@@ -4025,6 +4092,15 @@
     "Modified: / 22-12-2010 / 12:24:54 / sr"
 !
 
+nextBytes: bytesToRead of: zmember startingAt: pos into: b startingAt: off
+
+    stream position: (self dataStartOf: zmember) + startOfArchive + pos.
+    ^ stream nextBytes: bytesToRead into: b startingAt: off.
+
+    "Created: / 01-05-2011 / 16:21:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 10-12-2012 / 05:41:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 restoreOsDirectory:osDirectoryName fromArchiveDirectory: archiveDirectoryName
     |osDirectory directoryAlreadyCreated archiveDirectoryNameSize|
 
@@ -4085,7 +4161,7 @@
 withPositionAndMemberFor:fileName do:aBlock
     |zmemb dataStart|
 
-    (file isNil or:[mode ~~ #read]) ifTrue:[
+    (stream isNil or:[mode ~~ #read]) ifTrue:[
         ^ self error: 'ZipArchive not open for reading ...'.
     ].    
 
@@ -4093,9 +4169,10 @@
     zmemb isNil ifTrue:[^ nil].
 
     dataStart := self dataStartOf:zmemb.
-    aBlock value:zmemb value:dataStart.
+    ^ aBlock value:zmemb value:dataStart.
 
     "Created: / 21-11-2010 / 11:51:41 / cg"
+    "Modified: / 17-02-2017 / 22:57:43 / stefan"
 ! !
 
 !ZipArchive methodsFor:'reading - stream'!
@@ -4108,7 +4185,7 @@
         do:[:zmemb :position |
             |buffer rdSize compressionMethod nextBlockSize streamBufferSize myZipStream|
 
-            file position:position.
+            stream position:position.
 
             compressionMethod := zmemb compressionMethod.
             rdSize := zmemb uncompressedSize.
@@ -4122,12 +4199,12 @@
 
                     compressionMethod == COMPRESSION_DEFLATED ifTrue:[
                         myZipStream isNil ifTrue: [
-                            file binary.
-                            myZipStream := ZipStream readOpenAsZipStreamOn:file suppressHeaderAndChecksum:true.
+                            stream binary.
+                            myZipStream := ZipStream readOpenAsZipStreamOn:stream suppressHeaderAndChecksum:true.
                         ].
                         myZipStream next:nextBlockSize into:buffer startingAt:1.
                     ] ifFalse:[compressionMethod == COMPRESSION_STORED ifTrue:[
-                        file nextBytes:nextBlockSize into:buffer startingAt:1.
+                        stream nextBytes:nextBlockSize into:buffer startingAt:1.
                     ] ifFalse:[
                         UnsupportedZipFileFormatErrorSignal raiseErrorString:'unsupported compressMethod'
                     ]].
@@ -4150,7 +4227,7 @@
 
     |zipEntry dataStart|
 
-    (file isNil or:[mode ~~ #read]) ifTrue:[
+    (stream isNil or:[mode ~~ #read]) ifTrue:[
         ^ OpenError raiseRequestWith:nameOfFileInArchive errorString:'ZipArchive not open for reading ...'.
     ].    
 
@@ -4160,21 +4237,22 @@
     ].
 
     dataStart := self dataStartOf:zipEntry.
-    file position:dataStart.
-
-    ^ (ZipReadStream zipFileStream:file zipEntry:zipEntry)
-        zipArchive:self.
+    stream position:dataStart.
+
+    ^ (ZipReadStream zipFileStream:stream zipEntry:zipEntry) zipArchive:self.
+
+    "Modified (format): / 17-02-2017 / 22:52:00 / stefan"
 !
 
 reopenAndExtract:fileName intoStream: aWriteStream
     "extract an entry indentified by filename into aWriteStream"
 
-    file isNil ifTrue:[
+    stream isNil ifTrue:[
         self reopenForReading.
     ].
     self extract:fileName intoStream: aWriteStream.
-    file close.
-    file := nil.
+    stream close.
+    stream := nil.
 
     "Created: / 21-11-2010 / 11:59:04 / cg"
 ! !
@@ -4243,7 +4321,7 @@
     |zipEntry theZipFileName theCompressMethod streamBufferSize buffer 
      crc32 unCompressedDataSize startDataPosition nextBlockSize myZipStream|
 
-    (file isNil or: [mode ~~ #write]) ifTrue: [
+    (stream isNil or: [mode ~~ #write]) ifTrue: [
         ^ self error: 'ZipArchive not open for writing ...'.
     ].
 
@@ -4275,15 +4353,15 @@
     zipEntry setModificationTimeAndDateToNow.
 
     "/ ensure that the file position is at the end
-    file setToEnd.
-
-    zipEntry writeTo:file.
+    stream setToEnd.
+
+    zipEntry writeTo:stream.
 
     streamBufferSize := self class streamBufferSize.    
     buffer := ByteArray new:streamBufferSize.
     crc32 := 0.
     unCompressedDataSize := 0.
-    startDataPosition := file position.
+    startDataPosition := stream position.
 
     [
         [aStream atEnd] whileFalse: [
@@ -4294,11 +4372,11 @@
                 crc32 := ZipStream crc32BytesIn: buffer from:1 to:nextBlockSize crc:crc32.
                 theCompressMethod == COMPRESSION_DEFLATED ifTrue: [
                     myZipStream isNil ifTrue: [
-                        myZipStream := ZipStream writeOpenAsZipStreamOn:file suppressHeaderAndChecksum:true.
+                        myZipStream := ZipStream writeOpenAsZipStreamOn:stream suppressHeaderAndChecksum:true.
                     ].
                     myZipStream nextPutBytes:nextBlockSize from:buffer startingAt:1.
                 ] ifFalse: [theCompressMethod == COMPRESSION_STORED ifTrue: [
-                    file nextPutBytes:nextBlockSize from:buffer startingAt:1.
+                    stream nextPutBytes:nextBlockSize from:buffer startingAt:1.
                 ] ifFalse:[
                     UnsupportedZipFileFormatErrorSignal raiseRequestErrorString:'unsupported compressMethod'.
                 ]].
@@ -4310,16 +4388,16 @@
         ].
     ].
 
-    zipEntry compressedSize:(file position) - startDataPosition.
+    zipEntry compressedSize:(stream position) - startDataPosition.
 
     "/ crc32 is always required (not as written in docu to be zero in case of uncompressed mode)
     zipEntry crc32:crc32.
     zipEntry uncompressedSize: unCompressedDataSize.
 
-    zipEntry rewriteCrcAndSizeTo:file.
+    zipEntry rewriteCrcAndSizeTo:stream.
     self addMember:zipEntry.
 
-    file setToEnd.
+    stream setToEnd.
 
     "Modified: / 19-11-2010 / 15:39:32 / cg"
 !
@@ -4361,7 +4439,7 @@
     
     | zipEntry theCompressedData theZipFileName theCompressMethod  compressedDataOffset|
 
-    (file isNil or:[ mode ~~ #write ]) ifTrue:[
+    (stream isNil or:[ mode ~~ #write ]) ifTrue:[
         ^ self error:'ZipArchive not open for writing ...'.
     ].
     theCompressMethod := theCompressMethodArg.
@@ -4414,10 +4492,10 @@
     ].
     
     "/ ensure that the file position is at the end
-    file setToEnd.
-    zipEntry writeTo:file.
+    stream setToEnd.
+    zipEntry writeTo:stream.
     theCompressedData notNil ifTrue:[
-        file nextPutBytes:zipEntry compressedSize from:theCompressedData startingAt:compressedDataOffset.
+        stream nextPutBytes:zipEntry compressedSize from:theCompressedData startingAt:compressedDataOffset.
     ].
     self addMember:zipEntry.
 
@@ -4441,7 +4519,7 @@
 
     |zipEntry theZipFileName theCompressMethod|
 
-    (file isNil or:[mode ~~ #write]) ifTrue: [
+    (stream isNil or:[mode ~~ #write]) ifTrue: [
         ^ self error: 'ZipArchive not open for writing ...'.
     ].
 
@@ -4468,12 +4546,12 @@
     zipEntry setModificationTimeAndDateToNow.
 
     "/ ensure that the file position is at the end
-    file setToEnd.
-
-    zipEntry writeTo:file.
+    stream setToEnd.
+
+    zipEntry writeTo:stream.
     self addMember:zipEntry.
 
-    ^ (ZipWriteStream zipFileStream:file zipEntry:zipEntry) zipArchive:self.
+    ^ (ZipWriteStream zipFileStream:stream zipEntry:zipEntry) zipArchive:self.
 
     "Modified: / 19-11-2010 / 15:38:54 / cg"
 ! !