ZipArchive.st
changeset 1995 93f2f08bceb3
parent 1994 76336287ae17
child 2003 051486962c69
equal deleted inserted replaced
1994:76336287ae17 1995:93f2f08bceb3
  1245                                                         [exEnd]
  1245                                                         [exEnd]
  1246 
  1246 
  1247 "
  1247 "
  1248 !
  1248 !
  1249 
  1249 
       
  1250 examples2
       
  1251 "
       
  1252     add to new zip archive a entry which is located in memory using selector
       
  1253         addFile:'crcTest_resume_compressed.txt' withContents:
       
  1254     and real file contents from disk identified by a readStream using selector
       
  1255         addFile:rdStreamFile fromStream:
       
  1256                                                         [exBegin]
       
  1257     |zipwr testDirectory testFileWr rdStreamFile rdFileStream |
       
  1258 
       
  1259     testDirectory := 'C:\Dokumente und Einstellungen\stefan\Eigene Dateien\tmp\'.
       
  1260     testFileWr := 'streamtest_uncompressed.zip'.
       
  1261     rdStreamFile := 'projects.zip'.
       
  1262 
       
  1263     rdFileStream := ('C:\Dokumente und Einstellungen\stefan\Eigene Dateien\tmp\', rdStreamFile) asFilename readStream.
       
  1264     zipwr := ZipArchive newFileNamed:(testDirectory, testFileWr).
       
  1265     zipwr addFile:'crcTest_resume_compressed.txt' withContents: 'resume'.
       
  1266     zipwr addFile:rdStreamFile fromStream: rdFileStream.
       
  1267 
       
  1268     zipwr closeFile.
       
  1269                                                         [exEnd]
       
  1270 
       
  1271     read from zip archive a entry which into memory using selector
       
  1272         extract:'crcTest_resume_compressed.txt'
       
  1273     and store real file contents from disk using a readStream on archive contents entry
       
  1274         readStreamFor: rdStreamFile 
       
  1275                                                         [exBegin]
       
  1276     |ziprd testDirectory testFileRd wrStreamFile wrFileStream archiveRdStream data1
       
  1277      buffer streamAtEnd nextBlockSize |
       
  1278 
       
  1279     testDirectory := 'C:\Dokumente und Einstellungen\stefan\Eigene Dateien\tmp\'.
       
  1280     testFileRd := 'streamtest_uncompressed.zip'.
       
  1281     wrStreamFile := 'test_projects.zip'.
       
  1282 
       
  1283     ziprd := ZipArchive oldFileNamed:(testDirectory, testFileRd).
       
  1284     data1 := ziprd extract:'crcTest_resume_compressed.txt'.
       
  1285 
       
  1286     wrFileStream := ('C:\Dokumente und Einstellungen\stefan\Eigene Dateien\tmp\', wrStreamFile) asFilename writeStream.
       
  1287     (ziprd extract:'projects.zip' intoStream: wrFileStream) ifFalse: [
       
  1288         self halt.
       
  1289     ].
       
  1290 
       
  1291     ziprd closeFile.
       
  1292                                                         [exEnd]
       
  1293 
       
  1294 "
       
  1295 !
       
  1296 
  1250 fileFormatDescription
  1297 fileFormatDescription
  1251 
  1298 
  1252 "/File:    APPNOTE.TXT - .ZIP File Format Specification
  1299 "/File:    APPNOTE.TXT - .ZIP File Format Specification
  1253 "/Version: 6.3.2 
  1300 "/Version: 6.3.2 
  1254 "/Revised: September 28, 2007
  1301 "/Revised: September 28, 2007
  2900 
  2947 
  2901 centralDirectoryMinimumSize
  2948 centralDirectoryMinimumSize
  2902     ^ 46
  2949     ^ 46
  2903 
  2950 
  2904     "Created: / 29.3.1998 / 19:11:20 / cg"
  2951     "Created: / 29.3.1998 / 19:11:20 / cg"
       
  2952 !
       
  2953 
       
  2954 streamBufferSize
       
  2955     ^ 65536     "/ 1024 * 64
       
  2956 
       
  2957     "Created: / 29.3.1998 / 19:11:20 / cg"
  2905 ! !
  2958 ! !
  2906 
  2959 
  2907 !ZipArchive class methodsFor:'debugging'!
  2960 !ZipArchive class methodsFor:'debugging'!
  2908 
  2961 
  2909 debugTrace:aBoolean
  2962 debugTrace:aBoolean
  3608 ! !
  3661 ! !
  3609 
  3662 
  3610 !ZipArchive methodsFor:'reading'!
  3663 !ZipArchive methodsFor:'reading'!
  3611 
  3664 
  3612 extract:fileName
  3665 extract:fileName
  3613     "extract a filename entry as a byteArray;
  3666     "extract an entry identified by fileName as a byteArray;
  3614      nil on errors"
  3667      nil on errors"
  3615 
  3668 
  3616     |zmemb rawContents data|
  3669     |zmemb rawContents data|
  3617 
  3670 
  3618     (file isNil or: [mode ~~ #read]) ifTrue: [
  3671     (file isNil or: [mode ~~ #read]) ifTrue: [
  3638                 size:(zmemb uncompressedSize).
  3691                 size:(zmemb uncompressedSize).
  3639 
  3692 
  3640     ^ data.
  3693     ^ data.
  3641 !
  3694 !
  3642 
  3695 
       
  3696 extract:fileName intoStream: aWriteStream
       
  3697     "extract a entry indentified by filename into write stream
       
  3698       return false on error
       
  3699     "
       
  3700 
       
  3701     |zmemb rawContents data buffer rdSize nextBlockSize streamBufferSize|
       
  3702 
       
  3703     (file isNil or: [mode ~~ #read]) ifTrue: [
       
  3704         self error: 'Archiv not open for reading ...'.
       
  3705         ^ false
       
  3706     ].    
       
  3707 
       
  3708     zmemb := self findMember:fileName.
       
  3709     zmemb isNil ifTrue:[^ false].
       
  3710 
       
  3711     (zmemb fileStart + startOfArchive) > endOfArchive ifTrue: [
       
  3712         ZipFileFormatErrorSignal raiseRequestErrorString:' - zipEntry start is out of the archive bounds'.
       
  3713         ^ false
       
  3714     ].
       
  3715 
       
  3716     (zmemb fileStart + startOfArchive + (zmemb compressedSize)) > endOfArchive ifTrue: [
       
  3717         ZipFileFormatErrorSignal raiseRequestErrorString:' - zipEntry end is out of the archive bounds'.
       
  3718         ^ false
       
  3719     ].
       
  3720 
       
  3721     file position0Based:(zmemb fileStart + startOfArchive).
       
  3722 
       
  3723     zmemb compressionMethod == 8 ifTrue: [
       
  3724         self shouldImplement.
       
  3725         rawContents := file nextBytes:(zmemb compressedSize).
       
  3726         data := self
       
  3727                     decode:rawContents
       
  3728                     method:(zmemb compressionMethod)
       
  3729                     size:(zmemb uncompressedSize).
       
  3730         ^ false
       
  3731     ].
       
  3732 
       
  3733     rdSize := zmemb compressedSize.
       
  3734     streamBufferSize := self class streamBufferSize.    
       
  3735     buffer := ByteArray new: streamBufferSize.
       
  3736     [rdSize > 0] whileTrue: [
       
  3737         rdSize > (self class streamBufferSize) ifTrue: [
       
  3738             nextBlockSize := streamBufferSize.
       
  3739         ] ifFalse: [
       
  3740             (nextBlockSize := rdSize) > 0 ifTrue: [
       
  3741                 buffer := ByteArray new: nextBlockSize.
       
  3742             ].
       
  3743         ].
       
  3744         nextBlockSize > 0 ifTrue: [
       
  3745             file nextBytes:nextBlockSize into:buffer startingAt:1.
       
  3746             aWriteStream nextPutBytes:nextBlockSize from:buffer startingAt:1.
       
  3747         ].
       
  3748         rdSize := rdSize - nextBlockSize.
       
  3749     ].
       
  3750 
       
  3751     ^ true.
       
  3752 !
       
  3753 
  3643 extractArchive:fileName
  3754 extractArchive:fileName
  3644     "extract a filename entry as a byteArray;
  3755     "extract a filename entry as a byteArray;
  3645      nil on errors"
  3756      nil on errors"
  3646     |zmemb|
  3757     |zmemb|
  3647 
  3758 
  3663     "/ this can now be handled like an ordenary archive
  3774     "/ this can now be handled like an ordenary archive
  3664 
  3775 
  3665     ^ self class oldFileNamed:archiveName 
  3776     ^ self class oldFileNamed:archiveName 
  3666                startOfArchive:(zmemb fileStart + startOfArchive) 
  3777                startOfArchive:(zmemb fileStart + startOfArchive) 
  3667                  endOfArchive:(zmemb fileStart + startOfArchive + (zmemb compressedSize)).
  3778                  endOfArchive:(zmemb fileStart + startOfArchive + (zmemb compressedSize)).
  3668 !
       
  3669 
       
  3670 readStreamFor:nameOfFileInArchive
       
  3671     "open a stream on archive contents identified by nameOfFileInArchive"
       
  3672 
       
  3673     |zmemb rs zs|
       
  3674 
       
  3675     (file isNil or: [mode ~~ #read]) ifTrue: [
       
  3676         ^ self error: 'Archiv not open for reading ...'.
       
  3677     ].    
       
  3678 
       
  3679     zmemb := self findMember:nameOfFileInArchive.
       
  3680     zmemb isNil ifTrue:[^ nil].
       
  3681 
       
  3682     zmemb compressionMethod == 0 ifTrue: [
       
  3683         rs := ZipUncompressedArchiveStream readonlyFileNamed: archiveName asFilename.
       
  3684         rs position0Based:zmemb fileStart.
       
  3685         rs readLimit:(zmemb fileStart + zmemb uncompressedSize).
       
  3686         ^ rs
       
  3687     ].
       
  3688 
       
  3689     zs := ZipCompressedArchiveStream readOpenOn:rs 
       
  3690                                        position:zmemb fileStart 
       
  3691                                       readLimit:zmemb compressedSize.
       
  3692     ^ zs
       
  3693 !
  3779 !
  3694 
  3780 
  3695 restoreContentsFromZipDirectory:zipDirectoryName intoDirectory:intoDirectory
  3781 restoreContentsFromZipDirectory:zipDirectoryName intoDirectory:intoDirectory
  3696     "restore the contents of a file or directory (recursive) from zip archive -> zipDirectoryName 
  3782     "restore the contents of a file or directory (recursive) from zip archive -> zipDirectoryName 
  3697      into directory -> intoDirectory"
  3783      into directory -> intoDirectory"
  3698     intoDirectory exists ifFalse: [
  3784     intoDirectory exists ifFalse: [
  3699         ^ false
  3785         ^ false
  3700     ].
  3786     ].
  3701     ^ true
  3787     ^ true
       
  3788 ! !
       
  3789 
       
  3790 !ZipArchive methodsFor:'reading - stream'!
       
  3791 
       
  3792 readStreamFor:nameOfFileInArchive
       
  3793     "open a stream on archive contents identified by nameOfFileInArchive"
       
  3794     self shouldImplement.
       
  3795 "/
       
  3796 "/    |zmemb rs zs|
       
  3797 "/
       
  3798 "/    (file isNil or: [mode ~~ #read]) ifTrue: [
       
  3799 "/        ^ self error: 'Archiv not open for reading ...'.
       
  3800 "/    ].    
       
  3801 "/
       
  3802 "/    zmemb := self findMember:nameOfFileInArchive.
       
  3803 "/    zmemb isNil ifTrue:[^ nil].
       
  3804 "/
       
  3805 "/    zmemb compressionMethod == 0 ifTrue: [
       
  3806 "/        rs := ZipUncompressedArchiveStream readonlyFileNamed: archiveName asFilename.
       
  3807 "/        rs position0Based:zmemb fileStart.
       
  3808 "/        rs readLimit:(zmemb fileStart + zmemb uncompressedSize).
       
  3809 "/        ^ rs
       
  3810 "/    ].
       
  3811 "/
       
  3812 "/    "/ did not work right now proberly
       
  3813 "/    zs := ZipCompressedArchiveStream readOpenOn:rs 
       
  3814 "/                                       position:zmemb fileStart 
       
  3815 "/                                      readLimit:zmemb compressedSize.
       
  3816 "/    ^ zs
  3702 ! !
  3817 ! !
  3703 
  3818 
  3704 !ZipArchive methodsFor:'writing'!
  3819 !ZipArchive methodsFor:'writing'!
  3705 
  3820 
  3706 addContentsFromFileOrDirectory:realFileOrDirectoryName toZipDirectory:zipDirectoryName
  3821 addContentsFromFileOrDirectory:realFileOrDirectoryName toZipDirectory:zipDirectoryName
  3720     ^ true
  3835     ^ true
  3721 !
  3836 !
  3722 
  3837 
  3723 addDirectory: aDirectoryName
  3838 addDirectory: aDirectoryName
  3724     ^ self addFile: aDirectoryName withContents: nil compressMethod: 0 asDirectory: true.
  3839     ^ self addFile: aDirectoryName withContents: nil compressMethod: 0 asDirectory: true.
       
  3840 !
       
  3841 
       
  3842 addFile: aFileName fromStream: aStream
       
  3843     ^ self addFile: aFileName fromStream: aStream compressMethod: 0
       
  3844 !
       
  3845 
       
  3846 addFile: aFileName fromStream: aStream compressMethod: theCompressMethod
       
  3847     |zipEntry curTime curDate crc32Pos crc32 unCompressedDataSize
       
  3848       compressedDataSize buffer rdSize nextBlockSize streamBufferSize|
       
  3849 
       
  3850     (file isNil or: [mode ~~ #write]) ifTrue: [
       
  3851         ^ self error: 'Archiv not open for writing ...'.
       
  3852     ].
       
  3853     zipEntry := ZipMember new default.
       
  3854 
       
  3855     firstEntry isNil ifTrue: [
       
  3856         firstEntry := zipEntry.
       
  3857     ] ifFalse: [
       
  3858         lastEntry next: zipEntry.
       
  3859     ].
       
  3860 
       
  3861     lastEntry := zipEntry.
       
  3862 
       
  3863     zipEntry fileName: aFileName.
       
  3864     zipEntry fileNameLength: aFileName size.
       
  3865     zipEntry uncompressedSize: 0.
       
  3866 
       
  3867     zipEntry compressionMethod: theCompressMethod.
       
  3868     zipEntry internalFileAttributes: 1.
       
  3869     zipEntry externalFileAttributes: 32.
       
  3870 
       
  3871     curTime := Time now.
       
  3872     curDate := Date today.
       
  3873     "/ data and time in msdos format
       
  3874     zipEntry lastModFileTime: (((curTime seconds // 2) bitOr: (curTime minutes rightShift: -5)) bitOr: (curTime hours rightShift: -11)).
       
  3875     zipEntry lastModFileDate: (((curDate day) bitOr: (curDate month rightShift: -5)) bitOr: (((curDate year) - 1980) rightShift: -9)).
       
  3876 
       
  3877     "/ ensure that the file position is at the end
       
  3878     file setToEnd.
       
  3879 
       
  3880     zipEntry relativeLocalHeaderOffset:(file position).
       
  3881     file nextPutLong: 16r04034b50  MSB:false.
       
  3882     file nextPutShort:zipEntry versionNeedToExtract MSB:false.
       
  3883     file nextPutShort:zipEntry generalPurposBitFlag MSB:false.
       
  3884     file nextPutShort:zipEntry compressionMethod MSB:false.
       
  3885     file nextPutShort:zipEntry lastModFileTime MSB:false.
       
  3886     file nextPutShort:zipEntry lastModFileDate MSB:false.
       
  3887     crc32Pos := file position.
       
  3888     file nextPutLong:zipEntry crc32 MSB:false.
       
  3889     file nextPutLong:zipEntry compressedSize MSB:false.
       
  3890     file nextPutLong:zipEntry uncompressedSize MSB:false.
       
  3891     file nextPutShort:zipEntry fileNameLength MSB:false.
       
  3892     file nextPutShort:zipEntry extraFieldLength MSB:false.
       
  3893     file nextPutAll:zipEntry fileName.
       
  3894     zipEntry extraField notNil ifTrue: [
       
  3895         file nextPutAll:zipEntry extraField.
       
  3896     ].
       
  3897 
       
  3898     (theCompressMethod == 8) ifTrue: [
       
  3899         self shouldImplement.
       
  3900 "/        |tmpCompressedData tmpCompressedDataSize|
       
  3901 "/        tmpCompressedData := ByteArray new:(data size + 16). "/ if the compression is less then the additional overhead we need more space in buffer
       
  3902 "/        tmpCompressedDataSize := ZipStream compress:data into:tmpCompressedData.
       
  3903 "/
       
  3904 "/        zipEntry compressedSize: (tmpCompressedDataSize - 6). "/6 = the zlib specific data 2 bytes in front and 4 bytes behind the real data
       
  3905 "/        theCompressedData := tmpCompressedData copyFrom: 3. "/ 2 bytes before the real data
       
  3906     ] ifFalse: [
       
  3907         crc32 := 0.
       
  3908         streamBufferSize := self class streamBufferSize.    
       
  3909         buffer := ByteArray new: streamBufferSize.
       
  3910         rdSize := aStream size.
       
  3911         unCompressedDataSize := rdSize.
       
  3912         [rdSize > 0] whileTrue: [
       
  3913             rdSize > (self class streamBufferSize) ifTrue: [
       
  3914                 nextBlockSize := streamBufferSize.
       
  3915             ] ifFalse: [
       
  3916                 (nextBlockSize := rdSize) > 0 ifTrue:[
       
  3917                     buffer := ByteArray new: nextBlockSize.
       
  3918                 ].
       
  3919             ].
       
  3920             nextBlockSize > 0 ifTrue: [
       
  3921                 aStream nextBytes:nextBlockSize into:buffer startingAt:1.
       
  3922                 file nextPutBytes:nextBlockSize from:buffer startingAt:1.
       
  3923                 crc32 := (ZipStream crc32BytesIn: buffer crc: crc32).
       
  3924             ].
       
  3925             rdSize := rdSize - nextBlockSize.
       
  3926         ].
       
  3927         compressedDataSize := unCompressedDataSize.
       
  3928     ].
       
  3929 
       
  3930     zipEntry crc32: crc32.
       
  3931     zipEntry uncompressedSize: unCompressedDataSize.
       
  3932     zipEntry compressedSize: compressedDataSize.
       
  3933 
       
  3934     file position0Based:crc32Pos.
       
  3935 
       
  3936     file nextPutLong:zipEntry crc32 MSB:false.
       
  3937     file nextPutLong:zipEntry compressedSize MSB:false.
       
  3938     file nextPutLong:zipEntry uncompressedSize MSB:false.
       
  3939 
       
  3940     file setToEnd.
  3725 !
  3941 !
  3726 
  3942 
  3727 addFile: aFileName withContents: data
  3943 addFile: aFileName withContents: data
  3728     ^ self addFile: aFileName withContents: data compressMethod: 8 asDirectory: false.
  3944     ^ self addFile: aFileName withContents: data compressMethod: 8 asDirectory: false.
  3729 !
  3945 !
  3800     ].
  4016     ].
  3801 
  4017 
  3802     theCompressedData notNil ifTrue: [
  4018     theCompressedData notNil ifTrue: [
  3803         file nextPutBytes: zipEntry compressedSize from: theCompressedData.
  4019         file nextPutBytes: zipEntry compressedSize from: theCompressedData.
  3804     ].
  4020     ].
       
  4021 ! !
       
  4022 
       
  4023 !ZipArchive methodsFor:'writing - stream'!
       
  4024 
       
  4025 writeStreamFor:nameOfFileInArchive
       
  4026     "create new entry in central directory"
       
  4027     self shouldImplement.
       
  4028 "/    |zipEntry curTime curDate|
       
  4029 "/
       
  4030 "/    (file isNil or: [mode ~~ #write]) ifTrue: [
       
  4031 "/        ^ self error: 'Archiv not open for writing ...'.
       
  4032 "/    ].
       
  4033 "/    zipEntry := ZipMember new default.
       
  4034 "/
       
  4035 "/    firstEntry isNil ifTrue: [
       
  4036 "/        firstEntry := zipEntry.
       
  4037 "/    ] ifFalse: [
       
  4038 "/        lastEntry next: zipEntry.
       
  4039 "/    ].
       
  4040 "/
       
  4041 "/    lastEntry := zipEntry.
       
  4042 "/
       
  4043 "/    zipEntry fileName: nameOfFileInArchive.
       
  4044 "/    zipEntry fileNameLength: nameOfFileInArchive size.
       
  4045 "/    zipEntry uncompressedSize: 0.
       
  4046 "/
       
  4047 "/    zipEntry compressionMethod: 0.
       
  4048 "/    zipEntry internalFileAttributes: 1.
       
  4049 "/    zipEntry externalFileAttributes: 32.
       
  4050 "/
       
  4051 "/    curTime := Time now.
       
  4052 "/    curDate := Date today.
       
  4053 "/    "/ data and time in msdos format
       
  4054 "/    zipEntry lastModFileTime: (((curTime seconds // 2) bitOr: (curTime minutes rightShift: -5)) bitOr: (curTime hours rightShift: -11)).
       
  4055 "/    zipEntry lastModFileDate: (((curDate day) bitOr: (curDate month rightShift: -5)) bitOr: (((curDate year) - 1980) rightShift: -9)).
       
  4056 "/
       
  4057 "/    zipEntry compressedSize: zipEntry uncompressedSize.
       
  4058 "/
       
  4059 "/    "/ ensure that the file position is at the end
       
  4060 "/    file setToEnd.
       
  4061 "/
       
  4062 "/    zipEntry relativeLocalHeaderOffset:(file position).
       
  4063 "/    file nextPutLong: 16r04034b50  MSB:false.
       
  4064 "/    file nextPutShort:zipEntry versionNeedToExtract MSB:false.
       
  4065 "/    file nextPutShort:zipEntry generalPurposBitFlag MSB:false.
       
  4066 "/    file nextPutShort:zipEntry compressionMethod MSB:false.
       
  4067 "/    file nextPutShort:zipEntry lastModFileTime MSB:false.
       
  4068 "/    file nextPutShort:zipEntry lastModFileDate MSB:false.
       
  4069 "/    file nextPutLong:zipEntry crc32 MSB:false.
       
  4070 "/    file nextPutLong:zipEntry compressedSize MSB:false.
       
  4071 "/    file nextPutLong:zipEntry uncompressedSize MSB:false.
       
  4072 "/    file nextPutShort:zipEntry fileNameLength MSB:false.
       
  4073 "/    file nextPutShort:zipEntry extraFieldLength MSB:false.
       
  4074 "/    file nextPutAll:zipEntry fileName.
       
  4075 "/    zipEntry extraField notNil ifTrue: [
       
  4076 "/        file nextPutAll:zipEntry extraField.
       
  4077 "/    ].
       
  4078 "/
       
  4079 "/    ^ file
  3805 ! !
  4080 ! !
  3806 
  4081 
  3807 !ZipArchive::ZipCentralDirectory methodsFor:'accessing'!
  4082 !ZipArchive::ZipCentralDirectory methodsFor:'accessing'!
  3808 
  4083 
  3809 centralDirectorySize
  4084 centralDirectorySize
  4263 ! !
  4538 ! !
  4264 
  4539 
  4265 !ZipArchive class methodsFor:'documentation'!
  4540 !ZipArchive class methodsFor:'documentation'!
  4266 
  4541 
  4267 version
  4542 version
  4268     ^ '$Header: /cvs/stx/stx/libbasic2/ZipArchive.st,v 1.62 2008-05-28 16:20:00 ab Exp $'
  4543     ^ '$Header: /cvs/stx/stx/libbasic2/ZipArchive.st,v 1.63 2008-05-30 08:59:59 ab Exp $'
  4269 ! !
  4544 ! !
  4270 
  4545 
  4271 ZipArchive initialize!
  4546 ZipArchive initialize!