zip-archive-0.3.1.1/src/0000755000000000000000000000000013077600042013047 5ustar0000000000000000zip-archive-0.3.1.1/src/Codec/0000755000000000000000000000000013077600042014064 5ustar0000000000000000zip-archive-0.3.1.1/src/Codec/Archive/0000755000000000000000000000000013121705773015454 5ustar0000000000000000zip-archive-0.3.1.1/tests/0000755000000000000000000000000013121705643013425 5ustar0000000000000000zip-archive-0.3.1.1/tests/test4/0000755000000000000000000000000013121674701014470 5ustar0000000000000000zip-archive-0.3.1.1/tests/test4/c/0000755000000000000000000000000013121674730014714 5ustar0000000000000000zip-archive-0.3.1.1/src/Codec/Archive/Zip.hs0000644000000000000000000010213413121705773016553 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE DeriveDataTypeable #-} ------------------------------------------------------------------------ -- | -- Module : Codec.Archive.Zip -- Copyright : John MacFarlane -- License : BSD3 -- -- Maintainer : John MacFarlane < jgm at berkeley dot edu > -- Stability : unstable -- Portability : so far only tested on GHC -- -- The zip-archive library provides functions for creating, modifying, -- and extracting files from zip archives. -- -- Certain simplifying assumptions are made about the zip archives: in -- particular, there is no support for encryption, zip files that span -- multiple disks, ZIP64, OS-specific file attributes, or compression -- methods other than Deflate. However, the library should be able to -- read the most common zip archives, and the archives it produces should -- be readable by all standard unzip programs. -- -- As an example of the use of the library, a standalone zip archiver -- and extracter, Zip.hs, is provided in the source distribution. -- -- For more information on the format of zip archives, consult -- ------------------------------------------------------------------------ module Codec.Archive.Zip ( -- * Data structures Archive (..) , Entry (..) , CompressionMethod (..) , ZipOption (..) , ZipException (..) , emptyArchive -- * Pure functions for working with zip archives , toArchive , toArchiveOrFail , fromArchive , filesInArchive , addEntryToArchive , deleteEntryFromArchive , findEntryByPath , fromEntry , toEntry -- * IO functions for working with zip archives , readEntry , writeEntry , addFilesToArchive , extractFilesFromArchive ) where import System.Time ( toUTCTime, addToClockTime, CalendarTime (..), ClockTime (..), TimeDiff (..) ) #if MIN_VERSION_directory(1,2,0) import Data.Time.Clock.POSIX ( utcTimeToPOSIXSeconds ) #endif import Data.Bits ( shiftL, shiftR, (.&.) ) import Data.Binary import Data.Binary.Get import Data.Binary.Put import Data.List ( nub, find, intercalate ) import Data.Data (Data) import Data.Typeable (Typeable) import Text.Printf import System.FilePath import System.Directory ( doesDirectoryExist, getDirectoryContents, createDirectoryIfMissing ) import Control.Monad ( when, unless, zipWithM ) import qualified Control.Exception as E import System.Directory ( getModificationTime ) import System.IO ( stderr, hPutStrLn ) import qualified Data.Digest.CRC32 as CRC32 import qualified Data.Map as M #if MIN_VERSION_binary(0,6,0) import Control.Applicative #endif #ifndef _WINDOWS import System.Posix.Files ( setFileTimes, setFileMode, fileMode, getFileStatus ) #endif -- from bytestring import qualified Data.ByteString as S import qualified Data.ByteString.Lazy as B -- text import qualified Data.Text.Lazy as TL import qualified Data.Text.Lazy.Encoding as TL -- from zlib import qualified Codec.Compression.Zlib.Raw as Zlib versionMadeBy :: Word16 #ifdef _WINDOWS versionMadeBy = 0x0000 -- FAT/VFAT/VFAT32 file attributes #else versionMadeBy = 0x0300 -- UNIX file attributes #endif #if !MIN_VERSION_binary(0, 6, 0) manySig :: Word32 -> Get a -> Get [a] manySig sig p = do sig' <- lookAhead getWord32le if sig == sig' then do r <- p rs <- manySig sig p return $ r : rs else return [] #endif ------------------------------------------------------------------------ -- | Structured representation of a zip archive, including directory -- information and contents (in lazy bytestrings). data Archive = Archive { zEntries :: [Entry] -- ^ Files in zip archive , zSignature :: Maybe B.ByteString -- ^ Digital signature , zComment :: B.ByteString -- ^ Comment for whole zip archive } deriving (Read, Show) instance Binary Archive where put = putArchive get = getArchive -- | Representation of an archived file, including content and metadata. data Entry = Entry { eRelativePath :: FilePath -- ^ Relative path, using '/' as separator , eCompressionMethod :: CompressionMethod -- ^ Compression method , eLastModified :: Integer -- ^ Modification time (seconds since unix epoch) , eCRC32 :: Word32 -- ^ CRC32 checksum , eCompressedSize :: Word32 -- ^ Compressed size in bytes , eUncompressedSize :: Word32 -- ^ Uncompressed size in bytes , eExtraField :: B.ByteString -- ^ Extra field - unused by this library , eFileComment :: B.ByteString -- ^ File comment - unused by this library , eVersionMadeBy :: Word16 -- ^ Version made by field , eInternalFileAttributes :: Word16 -- ^ Internal file attributes - unused by this library , eExternalFileAttributes :: Word32 -- ^ External file attributes (system-dependent) , eCompressedData :: B.ByteString -- ^ Compressed contents of file } deriving (Read, Show, Eq) -- | Compression methods. data CompressionMethod = Deflate | NoCompression deriving (Read, Show, Eq) -- | Options for 'addFilesToArchive' and 'extractFilesFromArchive'. data ZipOption = OptRecursive -- ^ Recurse into directories when adding files | OptVerbose -- ^ Print information to stderr | OptDestination FilePath -- ^ Directory in which to extract | OptLocation FilePath Bool -- ^ Where to place file when adding files and whether to append current path deriving (Read, Show, Eq) data ZipException = CRC32Mismatch FilePath deriving (Show, Typeable, Data) instance E.Exception ZipException -- | A zip archive with no contents. emptyArchive :: Archive emptyArchive = Archive { zEntries = [] , zSignature = Nothing , zComment = B.empty } -- | Reads an 'Archive' structure from a raw zip archive (in a lazy bytestring). toArchive :: B.ByteString -> Archive toArchive = decode -- | Like 'toArchive', but returns an 'Either' value instead of raising an -- error if the archive cannot be decoded. NOTE: This function only -- works properly when the library is compiled against binary >= 0.7. -- With earlier versions, it will always return a Right value, -- raising an error if parsing fails. toArchiveOrFail :: B.ByteString -> Either String Archive #if MIN_VERSION_binary(0,7,0) toArchiveOrFail bs = case decodeOrFail bs of Left (_,_,e) -> Left e Right (_,_,x) -> Right x #else toArchiveOrFail bs = Right $ toArchive bs #endif -- | Writes an 'Archive' structure to a raw zip archive (in a lazy bytestring). fromArchive :: Archive -> B.ByteString fromArchive = encode -- | Returns a list of files in a zip archive. filesInArchive :: Archive -> [FilePath] filesInArchive = (map eRelativePath) . zEntries -- | Adds an entry to a zip archive, or updates an existing entry. addEntryToArchive :: Entry -> Archive -> Archive addEntryToArchive entry archive = let archive' = deleteEntryFromArchive (eRelativePath entry) archive oldEntries = zEntries archive' in archive' { zEntries = entry : oldEntries } -- | Deletes an entry from a zip archive. deleteEntryFromArchive :: FilePath -> Archive -> Archive deleteEntryFromArchive path archive = archive { zEntries = [e | e <- zEntries archive , not (eRelativePath e `matches` path)] } -- | Returns Just the zip entry with the specified path, or Nothing. findEntryByPath :: FilePath -> Archive -> Maybe Entry findEntryByPath path archive = find (\e -> path `matches` eRelativePath e) (zEntries archive) -- | Returns uncompressed contents of zip entry. fromEntry :: Entry -> B.ByteString fromEntry entry = decompressData (eCompressionMethod entry) (eCompressedData entry) -- | Create an 'Entry' with specified file path, modification time, and contents. toEntry :: FilePath -- ^ File path for entry -> Integer -- ^ Modification time for entry (seconds since unix epoch) -> B.ByteString -- ^ Contents of entry -> Entry toEntry path modtime contents = let uncompressedSize = B.length contents compressedData = compressData Deflate contents compressedSize = B.length compressedData -- only use compression if it helps! (compressionMethod, finalData, finalSize) = if uncompressedSize <= compressedSize then (NoCompression, contents, uncompressedSize) else (Deflate, compressedData, compressedSize) crc32 = CRC32.crc32 contents in Entry { eRelativePath = normalizePath path , eCompressionMethod = compressionMethod , eLastModified = modtime , eCRC32 = crc32 , eCompressedSize = fromIntegral finalSize , eUncompressedSize = fromIntegral uncompressedSize , eExtraField = B.empty , eFileComment = B.empty , eVersionMadeBy = 0 -- FAT , eInternalFileAttributes = 0 -- potentially non-text , eExternalFileAttributes = 0 -- appropriate if from stdin , eCompressedData = finalData } -- | Generates a 'Entry' from a file or directory. readEntry :: [ZipOption] -> FilePath -> IO Entry readEntry opts path = do isDir <- doesDirectoryExist path -- make sure directories end in / and deal with the OptLocation option let path' = let p = path ++ (case reverse path of ('/':_) -> "" _ | isDir -> "/" | otherwise -> "") in (case [(l,a) | OptLocation l a <- opts] of ((l,a):_) -> if a then l p else l takeFileName p _ -> p) contents <- if isDir then return B.empty else B.fromStrict <$> S.readFile path #if MIN_VERSION_directory(1,2,0) modEpochTime <- fmap (floor . utcTimeToPOSIXSeconds) $ getModificationTime path #else (TOD modEpochTime _) <- getModificationTime path #endif let entry = toEntry path' modEpochTime contents entryE <- #ifdef _WINDOWS return $ entry #else do fm <- fmap fileMode $ getFileStatus path let modes = fromIntegral $ shiftL (toInteger fm) 16 return $ entry { eExternalFileAttributes = modes, eVersionMadeBy = versionMadeBy } #endif when (OptVerbose `elem` opts) $ do let compmethod = case eCompressionMethod entryE of Deflate -> "deflated" NoCompression -> "stored" hPutStrLn stderr $ printf " adding: %s (%s %.f%%)" (eRelativePath entryE) compmethod (100 - (100 * compressionRatio entryE)) return entryE -- | Writes contents of an 'Entry' to a file. Throws a -- 'CRC32Mismatch' exception if the CRC32 checksum for the entry -- does not match the uncompressed data. writeEntry :: [ZipOption] -> Entry -> IO () writeEntry opts entry = do let path = case [d | OptDestination d <- opts] of (x:_) -> x eRelativePath entry _ -> eRelativePath entry -- create directories if needed let dir = takeDirectory path exists <- doesDirectoryExist dir unless exists $ do createDirectoryIfMissing True dir when (OptVerbose `elem` opts) $ hPutStrLn stderr $ " creating: " ++ dir if length path > 0 && last path == '/' -- path is a directory then return () else do when (OptVerbose `elem` opts) $ do hPutStrLn stderr $ case eCompressionMethod entry of Deflate -> " inflating: " ++ path NoCompression -> "extracting: " ++ path let uncompressedData = fromEntry entry if eCRC32 entry == CRC32.crc32 uncompressedData then B.writeFile path uncompressedData else E.throwIO $ CRC32Mismatch path #ifndef _WINDOWS let modes = fromIntegral $ shiftR (eExternalFileAttributes entry) 16 when (eVersionMadeBy entry .&. 0xFF00 == 0x0300 && modes /= 0) $ setFileMode path modes #endif -- Note that last modified times are supported only for POSIX, not for -- Windows. setFileTimeStamp path (eLastModified entry) -- | Add the specified files to an 'Archive'. If 'OptRecursive' is specified, -- recursively add files contained in directories. If 'OptVerbose' is specified, -- print messages to stderr. addFilesToArchive :: [ZipOption] -> Archive -> [FilePath] -> IO Archive addFilesToArchive opts archive files = do filesAndChildren <- if OptRecursive `elem` opts then mapM getDirectoryContentsRecursive files >>= return . nub . concat else return files entries <- mapM (readEntry opts) filesAndChildren return $ foldr addEntryToArchive archive entries -- | Extract all files from an 'Archive', creating directories -- as needed. If 'OptVerbose' is specified, print messages to stderr. -- Note that the last-modified time is set correctly only in POSIX, -- not in Windows. extractFilesFromArchive :: [ZipOption] -> Archive -> IO () extractFilesFromArchive opts archive = mapM_ (writeEntry opts) $ zEntries archive -------------------------------------------------------------------------------- -- Internal functions for reading and writing zip binary format. -- Note that even on Windows, zip files use "/" internally as path separator. normalizePath :: FilePath -> String normalizePath path = let dir = takeDirectory path fn = takeFileName path (_drive, dir') = splitDrive dir -- note: some versions of filepath return ["."] if no dir dirParts = filter (/=".") $ splitDirectories dir' in intercalate "/" (dirParts ++ [fn]) -- Equality modulo normalization. So, "./foo" `matches` "foo". matches :: FilePath -> FilePath -> Bool matches fp1 fp2 = normalizePath fp1 == normalizePath fp2 -- | Uncompress a lazy bytestring. compressData :: CompressionMethod -> B.ByteString -> B.ByteString compressData Deflate = Zlib.compress compressData NoCompression = id -- | Compress a lazy bytestring. decompressData :: CompressionMethod -> B.ByteString -> B.ByteString decompressData Deflate = Zlib.decompress decompressData NoCompression = id -- | Calculate compression ratio for an entry (for verbose output). compressionRatio :: Entry -> Float compressionRatio entry = if eUncompressedSize entry == 0 then 1 else fromIntegral (eCompressedSize entry) / fromIntegral (eUncompressedSize entry) -- | MSDOS datetime: a pair of Word16s (date, time) with the following structure: -- -- > DATE bit 0 - 4 5 - 8 9 - 15 -- > value day (1 - 31) month (1 - 12) years from 1980 -- > TIME bit 0 - 4 5 - 10 11 - 15 -- > value seconds* minute hour -- > *stored in two-second increments -- data MSDOSDateTime = MSDOSDateTime { msDOSDate :: Word16 , msDOSTime :: Word16 } deriving (Read, Show, Eq) -- | Epoch time corresponding to the minimum DOS DateTime (Jan 1 1980 00:00:00). minMSDOSDateTime :: Integer minMSDOSDateTime = 315532800 -- | Convert a clock time to a MSDOS datetime. The MSDOS time will be relative to UTC. epochTimeToMSDOSDateTime :: Integer -> MSDOSDateTime epochTimeToMSDOSDateTime epochtime | epochtime < minMSDOSDateTime = epochTimeToMSDOSDateTime minMSDOSDateTime -- if time is earlier than minimum DOS datetime, return minimum epochTimeToMSDOSDateTime epochtime = let ut = toUTCTime (TOD epochtime 0) dosTime = toEnum $ (ctSec ut `div` 2) + shiftL (ctMin ut) 5 + shiftL (ctHour ut) 11 dosDate = toEnum $ ctDay ut + shiftL (fromEnum (ctMonth ut) + 1) 5 + shiftL (ctYear ut - 1980) 9 in MSDOSDateTime { msDOSDate = dosDate, msDOSTime = dosTime } -- | Convert a MSDOS datetime to a 'ClockTime'. msDOSDateTimeToEpochTime :: MSDOSDateTime -> Integer msDOSDateTimeToEpochTime (MSDOSDateTime {msDOSDate = dosDate, msDOSTime = dosTime}) = let seconds = fromIntegral $ 2 * (dosTime .&. 0O37) minutes = fromIntegral $ (shiftR dosTime 5) .&. 0O77 hour = fromIntegral $ shiftR dosTime 11 day = fromIntegral $ dosDate .&. 0O37 month = fromIntegral $ ((shiftR dosDate 5) .&. 0O17) - 1 year = fromIntegral $ shiftR dosDate 9 timeSinceEpoch = TimeDiff { tdYear = year + 10, -- dos times since 1980, unix epoch starts 1970 tdMonth = month, tdDay = day - 1, -- dos days start from 1 tdHour = hour, tdMin = minutes, tdSec = seconds, tdPicosec = 0 } (TOD epochsecs _) = addToClockTime timeSinceEpoch (TOD 0 0) in epochsecs getDirectoryContentsRecursive :: FilePath -> IO [FilePath] getDirectoryContentsRecursive path = do isDir <- doesDirectoryExist path if isDir then do contents <- getDirectoryContents path let contents' = map (path ) $ filter (`notElem` ["..","."]) contents children <- mapM getDirectoryContentsRecursive contents' if path == "." then return (concat children) else return (path : concat children) else return [path] setFileTimeStamp :: FilePath -> Integer -> IO () setFileTimeStamp file epochtime = do #ifdef _WINDOWS return () -- TODO - figure out how to set the timestamp on Windows #else let epochtime' = fromInteger epochtime setFileTimes file epochtime' epochtime' #endif -- A zip file has the following format (*'d items are not supported in this implementation): -- -- > [local file header 1] -- > [file data 1] -- > [data descriptor 1*] -- > . -- > . -- > . -- > [local file header n] -- > [file data n] -- > [data descriptor n*] -- > [archive decryption header*] -- > [archive extra data record*] -- > [central directory] -- > [zip64 end of central directory record*] -- > [zip64 end of central directory locator*] -- > [end of central directory record] -- -- Files stored in arbitrary order. All values are stored in -- little-endian byte order unless otherwise specified. -- -- Central directory structure: -- -- > [file header 1] -- > . -- > . -- > . -- > [file header n] -- > [digital signature] -- -- End of central directory record: -- -- > end of central dir signature 4 bytes (0x06054b50) -- > number of this disk 2 bytes -- > number of the disk with the -- > start of the central directory 2 bytes -- > total number of entries in the -- > central directory on this disk 2 bytes -- > total number of entries in -- > the central directory 2 bytes -- > size of the central directory 4 bytes -- > offset of start of central -- > directory with respect to -- > the starting disk number 4 bytes -- > .ZIP file comment length 2 bytes -- > .ZIP file comment (variable size) getArchive :: Get Archive getArchive = do #if MIN_VERSION_binary(0,6,0) locals <- many getLocalFile files <- many (getFileHeader (M.fromList locals)) digSig <- Just `fmap` getDigitalSignature <|> return Nothing #else locals <- manySig 0x04034b50 getLocalFile files <- manySig 0x02014b50 (getFileHeader (M.fromList locals)) digSig <- lookAheadM getDigitalSignature #endif endSig <- getWord32le unless (endSig == 0x06054b50) $ fail "Did not find end of central directory signature" skip 2 -- disk number skip 2 -- disk number of central directory skip 2 -- num entries on this disk skip 2 -- num entries in central directory skip 4 -- central directory size skip 4 -- offset of central directory commentLength <- getWord16le zipComment <- getLazyByteString (toEnum $ fromEnum commentLength) return $ Archive { zEntries = files , zSignature = digSig , zComment = zipComment } putArchive :: Archive -> Put putArchive archive = do mapM_ putLocalFile $ zEntries archive let localFileSizes = map localFileSize $ zEntries archive let offsets = scanl (+) 0 localFileSizes let cdOffset = last offsets _ <- zipWithM putFileHeader offsets (zEntries archive) putDigitalSignature $ zSignature archive putWord32le 0x06054b50 putWord16le 0 -- disk number putWord16le 0 -- disk number of central directory putWord16le $ fromIntegral $ length $ zEntries archive -- number of entries this disk putWord16le $ fromIntegral $ length $ zEntries archive -- number of entries putWord32le $ sum $ map fileHeaderSize $ zEntries archive -- size of central directory putWord32le $ fromIntegral cdOffset -- offset of central dir putWord16le $ fromIntegral $ B.length $ zComment archive putLazyByteString $ zComment archive fileHeaderSize :: Entry -> Word32 fileHeaderSize f = fromIntegral $ 4 + 2 + 2 + 2 + 2 + 2 + 2 + 4 + 4 + 4 + 2 + 2 + 2 + 2 + 2 + 4 + 4 + fromIntegral (B.length $ fromString $ normalizePath $ eRelativePath f) + B.length (eExtraField f) + B.length (eFileComment f) localFileSize :: Entry -> Word32 localFileSize f = fromIntegral $ 4 + 2 + 2 + 2 + 2 + 2 + 4 + 4 + 4 + 2 + 2 + fromIntegral (B.length $ fromString $ normalizePath $ eRelativePath f) + B.length (eExtraField f) + B.length (eCompressedData f) -- Local file header: -- -- > local file header signature 4 bytes (0x04034b50) -- > version needed to extract 2 bytes -- > general purpose bit flag 2 bytes -- > compression method 2 bytes -- > last mod file time 2 bytes -- > last mod file date 2 bytes -- > crc-32 4 bytes -- > compressed size 4 bytes -- > uncompressed size 4 bytes -- > file name length 2 bytes -- > extra field length 2 bytes -- -- > file name (variable size) -- > extra field (variable size) -- -- Note that if bit 3 of the general purpose bit flag is set, then the -- compressed size will be 0 and the size will be stored instead in a -- data descriptor record AFTER the file contents. The record normally -- begins with the signature 0x08074b50, then 4 bytes crc-32, 4 bytes -- compressed size, 4 bytes uncompressed size. getLocalFile :: Get (Word32, B.ByteString) getLocalFile = do offset <- bytesRead getWord32le >>= ensure (== 0x04034b50) skip 2 -- version bitflag <- getWord16le skip 2 -- compressionMethod skip 2 -- last mod file time skip 2 -- last mod file date skip 4 -- crc32 compressedSize <- getWord32le when (compressedSize == 0xFFFFFFFF) $ fail "Can't read ZIP64 archive." skip 4 -- uncompressedsize fileNameLength <- getWord16le extraFieldLength <- getWord16le skip (fromIntegral fileNameLength) -- filename skip (fromIntegral extraFieldLength) -- extra field compressedData <- if bitflag .&. 0O10 == 0 then getLazyByteString (fromIntegral compressedSize) else -- If bit 3 of general purpose bit flag is set, -- then we need to read until we get to the -- data descriptor record. We assume that the -- record has signature 0x08074b50; this is not required -- by the specification but is common. do raw <- getWordsTilSig 0x08074b50 skip 4 -- crc32 cs <- getWord32le -- compressed size skip 4 -- uncompressed size if fromIntegral cs == B.length raw then return $ raw else fail "Content size mismatch in data descriptor record" return (fromIntegral offset, compressedData) getWordsTilSig :: Word32 -> Get B.ByteString #if MIN_VERSION_binary(0, 6, 0) getWordsTilSig sig = (B.fromChunks . reverse) `fmap` go Nothing [] where sig' = S.pack [fromIntegral $ sig .&. 0xFF, fromIntegral $ sig `shiftR` 8 .&. 0xFF, fromIntegral $ sig `shiftR` 16 .&. 0xFF, fromIntegral $ sig `shiftR` 24 .&. 0xFF] chunkSize = 16384 --chunkSize = 4 -- for testing prefix match checkChunk chunk = do -- find in content let (prefix, start) = S.breakSubstring sig' chunk if S.null start then return $ Right chunk else return $ Left $ S.length prefix go :: Maybe (Word8, Word8, Word8) -> [S.ByteString] -> Get [S.ByteString] go prefixes acc = do -- note: lookAheadE will rewind if the result is Left eitherChunkOrIndex <- lookAheadE $ do chunk <- getByteString chunkSize <|> B.toStrict `fmap` getRemainingLazyByteString case prefixes of Just (byte3,byte2,byte1) -> let len = S.length chunk in if len >= 1 && S.pack [byte3,byte2,byte1,S.index chunk 0] == sig' then return $ Left $ -3 else if len >= 2 && S.pack [byte2,byte1,S.index chunk 0,S.index chunk 1] == sig' then return $ Left $ -2 else if len >= 3 && S.pack [byte1,S.index chunk 0,S.index chunk 1,S.index chunk 2] == sig' then return $ Left $ -1 else checkChunk chunk Nothing -> checkChunk chunk case eitherChunkOrIndex of Left index -> if index < 0 then do -- prefix match skip (4 + index) -- skip over partial match in next chunk return $ (S.take (S.length (head acc) + index) (head acc)) : (tail acc) else do -- match inside this chunk lastchunk <- getByteString index -- must read again skip 4 return (lastchunk:acc) Right chunk -> if len == chunkSize then go prefixes' (chunk:acc) else fail $ "getWordsTilSig: signature not found before EOF" where len = S.length chunk prefixes' = Just $ (S.index chunk (len - 3), S.index chunk (len - 2), S.index chunk (len - 1)) #else getWordsTilSig sig = B.pack `fmap` go [] where go acc = do sig' <- lookAhead getWord32le if sig == sig' then skip 4 >> return (reverse acc) else do w <- getWord8 go (w:acc) #endif putLocalFile :: Entry -> Put putLocalFile f = do putWord32le 0x04034b50 putWord16le 20 -- version needed to extract (>=2.0) putWord16le 0x802 -- general purpose bit flag (bit 1 = max compression, bit 11 = UTF-8) putWord16le $ case eCompressionMethod f of NoCompression -> 0 Deflate -> 8 let modTime = epochTimeToMSDOSDateTime $ eLastModified f putWord16le $ msDOSTime modTime putWord16le $ msDOSDate modTime putWord32le $ eCRC32 f putWord32le $ eCompressedSize f putWord32le $ eUncompressedSize f putWord16le $ fromIntegral $ B.length $ fromString $ normalizePath $ eRelativePath f putWord16le $ fromIntegral $ B.length $ eExtraField f putLazyByteString $ fromString $ normalizePath $ eRelativePath f putLazyByteString $ eExtraField f putLazyByteString $ eCompressedData f -- File header structure: -- -- > central file header signature 4 bytes (0x02014b50) -- > version made by 2 bytes -- > version needed to extract 2 bytes -- > general purpose bit flag 2 bytes -- > compression method 2 bytes -- > last mod file time 2 bytes -- > last mod file date 2 bytes -- > crc-32 4 bytes -- > compressed size 4 bytes -- > uncompressed size 4 bytes -- > file name length 2 bytes -- > extra field length 2 bytes -- > file comment length 2 bytes -- > disk number start 2 bytes -- > internal file attributes 2 bytes -- > external file attributes 4 bytes -- > relative offset of local header 4 bytes -- -- > file name (variable size) -- > extra field (variable size) -- > file comment (variable size) getFileHeader :: M.Map Word32 B.ByteString -- ^ map of (offset, content) pairs returned by getLocalFile -> Get Entry getFileHeader locals = do getWord32le >>= ensure (== 0x02014b50) vmb <- getWord16le -- version made by versionNeededToExtract <- getWord8 skip 1 -- upper byte indicates OS part of "version needed to extract" unless (versionNeededToExtract <= 20) $ fail "This archive requires zip >= 2.0 to extract." skip 2 -- general purpose bit flag rawCompressionMethod <- getWord16le compressionMethod <- case rawCompressionMethod of 0 -> return NoCompression 8 -> return Deflate _ -> fail $ "Unknown compression method " ++ show rawCompressionMethod lastModFileTime <- getWord16le lastModFileDate <- getWord16le crc32 <- getWord32le compressedSize <- getWord32le uncompressedSize <- getWord32le fileNameLength <- getWord16le extraFieldLength <- getWord16le fileCommentLength <- getWord16le skip 2 -- disk number start internalFileAttributes <- getWord16le externalFileAttributes <- getWord32le relativeOffset <- getWord32le fileName <- getLazyByteString (toEnum $ fromEnum fileNameLength) extraField <- getLazyByteString (toEnum $ fromEnum extraFieldLength) fileComment <- getLazyByteString (toEnum $ fromEnum fileCommentLength) compressedData <- case (M.lookup relativeOffset locals) of Just x -> return x Nothing -> fail $ "Unable to find data at offset " ++ show relativeOffset return $ Entry { eRelativePath = toString fileName , eCompressionMethod = compressionMethod , eLastModified = msDOSDateTimeToEpochTime $ MSDOSDateTime { msDOSDate = lastModFileDate, msDOSTime = lastModFileTime } , eCRC32 = crc32 , eCompressedSize = compressedSize , eUncompressedSize = uncompressedSize , eExtraField = extraField , eFileComment = fileComment , eVersionMadeBy = vmb , eInternalFileAttributes = internalFileAttributes , eExternalFileAttributes = externalFileAttributes , eCompressedData = compressedData } putFileHeader :: Word32 -- ^ offset -> Entry -> Put putFileHeader offset local = do putWord32le 0x02014b50 putWord16le $ eVersionMadeBy local putWord16le 20 -- version needed to extract (>= 2.0) putWord16le 0x802 -- general purpose bit flag (bit 1 = max compression, bit 11 = UTF-8) putWord16le $ case eCompressionMethod local of NoCompression -> 0 Deflate -> 8 let modTime = epochTimeToMSDOSDateTime $ eLastModified local putWord16le $ msDOSTime modTime putWord16le $ msDOSDate modTime putWord32le $ eCRC32 local putWord32le $ eCompressedSize local putWord32le $ eUncompressedSize local putWord16le $ fromIntegral $ B.length $ fromString $ normalizePath $ eRelativePath local putWord16le $ fromIntegral $ B.length $ eExtraField local putWord16le $ fromIntegral $ B.length $ eFileComment local putWord16le 0 -- disk number start putWord16le $ eInternalFileAttributes local putWord32le $ eExternalFileAttributes local putWord32le offset putLazyByteString $ fromString $ normalizePath $ eRelativePath local putLazyByteString $ eExtraField local putLazyByteString $ eFileComment local -- Digital signature: -- -- > header signature 4 bytes (0x05054b50) -- > size of data 2 bytes -- > signature data (variable size) #if MIN_VERSION_binary(0,6,0) getDigitalSignature :: Get B.ByteString getDigitalSignature = do getWord32le >>= ensure (== 0x05054b50) sigSize <- getWord16le getLazyByteString (toEnum $ fromEnum sigSize) #else getDigitalSignature :: Get (Maybe B.ByteString) getDigitalSignature = do hdrSig <- getWord32le if hdrSig /= 0x05054b50 then return Nothing else do sigSize <- getWord16le getLazyByteString (toEnum $ fromEnum sigSize) >>= return . Just #endif putDigitalSignature :: Maybe B.ByteString -> Put putDigitalSignature Nothing = return () putDigitalSignature (Just sig) = do putWord32le 0x05054b50 putWord16le $ fromIntegral $ B.length sig putLazyByteString sig ensure :: (a -> Bool) -> a -> Get () ensure p val = if p val then return () else fail "ensure not satisfied" toString :: B.ByteString -> String toString = TL.unpack . TL.decodeUtf8 fromString :: String -> B.ByteString fromString = TL.encodeUtf8 . TL.pack zip-archive-0.3.1.1/Main.hs0000644000000000000000000000740513114765107013514 0ustar0000000000000000------------------------------------------------------------------------ -- Zip.hs -- Copyright (c) 2008 John MacFarlane -- License : BSD3 (see LICENSE) -- -- This is a demonstration of the use of the 'Codec.Archive.Zip' library. -- It duplicates some of the functionality of the 'zip' command-line -- program. ------------------------------------------------------------------------ import Codec.Archive.Zip import System.IO import qualified Data.ByteString.Lazy as B import System.Exit import System.Environment import System.Directory import System.Console.GetOpt import Control.Monad ( when ) import Control.Applicative ( (<$>) ) import Data.Version ( showVersion ) import Paths_zip_archive ( version ) import Debug.Trace ( traceShowId ) data Flag = Quiet | Version | Decompress | Recursive | Remove | List | Debug | Help deriving (Eq, Show, Read) options :: [OptDescr Flag] options = [ Option ['d'] ["decompress"] (NoArg Decompress) "decompress (unzip)" , Option ['r'] ["recursive"] (NoArg Recursive) "recursive" , Option ['R'] ["remove"] (NoArg Remove) "remove" , Option ['l'] ["list"] (NoArg List) "list" , Option ['v'] ["version"] (NoArg Version) "version" , Option ['q'] ["quiet"] (NoArg Quiet) "quiet" , Option [] ["debug"] (NoArg Debug) "debug output" , Option ['h'] ["help"] (NoArg Help) "help" ] main :: IO () main = do argv <- getArgs progname <- getProgName let header = "Usage: " ++ progname ++ " [OPTION...] archive files..." (opts, args) <- case getOpt Permute options argv of (o, _, _) | Version `elem` o -> do putStrLn ("version " ++ showVersion version) exitWith ExitSuccess (o, _, _) | Help `elem` o -> error $ usageInfo header options (o, (a:as), []) -> return (o, a:as) (_, _, errs) -> error $ concat errs ++ "\n" ++ usageInfo header options let verbosity = if Quiet `elem` opts then [] else [OptVerbose] let debug = Debug `elem` opts let cmd = case filter (`notElem` [Quiet, Help, Version, Debug]) opts of [] -> Recursive (x:_) -> x let (archivePath : files) = args exists <- doesFileExist archivePath archive <- if exists then toArchive <$> B.readFile archivePath else return emptyArchive let showArchiveIfDebug x = if debug then traceShowId x else x case cmd of Decompress -> extractFilesFromArchive verbosity $ showArchiveIfDebug archive Remove -> do tempDir <- getTemporaryDirectory (tempArchivePath, tempArchive) <- openTempFile tempDir "zip" B.hPut tempArchive $ fromArchive $ showArchiveIfDebug $ foldr deleteEntryFromArchive archive files hClose tempArchive copyFile tempArchivePath archivePath removeFile tempArchivePath List -> mapM_ putStrLn $ filesInArchive $ showArchiveIfDebug archive Recursive -> do when (null files) $ error "No files specified." tempDir <- getTemporaryDirectory (tempArchivePath, tempArchive) <- openTempFile tempDir "zip" addFilesToArchive (verbosity ++ [OptRecursive]) archive files >>= B.hPut tempArchive . fromArchive . showArchiveIfDebug hClose tempArchive copyFile tempArchivePath archivePath removeFile tempArchivePath _ -> error $ "Unknown command " ++ show cmd zip-archive-0.3.1.1/tests/test-zip-archive.hs0000644000000000000000000001334713121704227017164 0ustar0000000000000000{-# OPTIONS_GHC -fno-warn-orphans #-} {-# LANGUAGE CPP #-} -- Test suite for Codec.Archive.Zip -- runghc Test.hs import Codec.Archive.Zip import System.Directory import Test.HUnit.Base import Test.HUnit.Text import qualified Data.ByteString.Char8 as BS import qualified Data.ByteString.Lazy as BL import Control.Applicative import System.Exit import System.IO.Temp (withTempDirectory) #ifndef _WINDOWS import System.Posix.Files #endif -- define equality for Archives so timestamps aren't distinguished if they -- correspond to the same MSDOS datetime. instance Eq Archive where (==) a1 a2 = zSignature a1 == zSignature a2 && zComment a1 == zComment a2 && (all id $ zipWith (\x y -> x { eLastModified = eLastModified x `div` 2 } == y { eLastModified = eLastModified y `div` 2 }) (zEntries a1) (zEntries a2)) main :: IO Counts main = withTempDirectory "." "test-zip-archive." $ \tmpDir -> do res <- runTestTT $ TestList $ map (\f -> f tmpDir) [ testReadWriteArchive , testReadExternalZip , testFromToArchive , testReadWriteEntry , testAddFilesOptions , testDeleteEntries , testExtractFiles #ifndef _WINDOWS , testExtractFilesWithPosixAttrs #endif ] exitWith $ case (failures res + errors res) of 0 -> ExitSuccess n -> ExitFailure n testReadWriteArchive :: FilePath -> Test testReadWriteArchive tmpDir = TestCase $ do archive <- addFilesToArchive [OptRecursive] emptyArchive ["LICENSE", "src"] BL.writeFile (tmpDir ++ "/test1.zip") $ fromArchive archive archive' <- toArchive <$> BL.readFile (tmpDir ++ "/test1.zip") assertEqual "for writing and reading test1.zip" archive archive' assertEqual "for writing and reading test1.zip" archive archive' testReadExternalZip :: FilePath -> Test testReadExternalZip _tmpDir = TestCase $ do archive <- toArchive <$> BL.readFile "tests/test4.zip" let files = filesInArchive archive assertEqual "for results of filesInArchive" ["test4/","test4/a.txt","test4/b.bin","test4/c/", "test4/c/with spaces.txt"] files bContents <- BL.readFile "tests/test4/b.bin" case findEntryByPath "test4/b.bin" archive of Nothing -> assertFailure "test4/b.bin not found in archive" Just f -> assertEqual "for contents of test4/b.bin in archive" bContents (fromEntry f) case findEntryByPath "test4/" archive of Nothing -> assertFailure "test4/ not found in archive" Just f -> assertEqual "for contents of test4/ in archive" BL.empty (fromEntry f) testFromToArchive :: FilePath -> Test testFromToArchive _tmpDir = TestCase $ do archive <- addFilesToArchive [OptRecursive] emptyArchive ["LICENSE", "src"] assertEqual "for (toArchive $ fromArchive archive)" archive (toArchive $ fromArchive archive) testReadWriteEntry :: FilePath -> Test testReadWriteEntry tmpDir = TestCase $ do entry <- readEntry [] "zip-archive.cabal" setCurrentDirectory tmpDir writeEntry [] entry setCurrentDirectory ".." entry' <- readEntry [] (tmpDir ++ "/zip-archive.cabal") let entry'' = entry' { eRelativePath = eRelativePath entry, eLastModified = eLastModified entry } assertEqual "for readEntry -> writeEntry -> readEntry" entry entry'' testAddFilesOptions :: FilePath -> Test testAddFilesOptions _tmpDir = TestCase $ do archive1 <- addFilesToArchive [OptVerbose] emptyArchive ["LICENSE", "src"] archive2 <- addFilesToArchive [OptRecursive, OptVerbose] archive1 ["LICENSE", "src"] assertBool "for recursive and nonrecursive addFilesToArchive" (length (filesInArchive archive1) < length (filesInArchive archive2)) testDeleteEntries :: FilePath -> Test testDeleteEntries _tmpDir = TestCase $ do archive1 <- addFilesToArchive [] emptyArchive ["LICENSE", "src"] let archive2 = deleteEntryFromArchive "LICENSE" archive1 let archive3 = deleteEntryFromArchive "src" archive2 assertEqual "for deleteFilesFromArchive" emptyArchive archive3 testExtractFiles :: FilePath -> Test testExtractFiles tmpDir = TestCase $ do createDirectory (tmpDir ++ "/dir1") createDirectory (tmpDir ++ "/dir1/dir2") let hiMsg = BS.pack "hello there" let helloMsg = BS.pack "Hello there. This file is very long. Longer than 31 characters." BS.writeFile (tmpDir ++ "/dir1/hi") hiMsg BS.writeFile (tmpDir ++ "/dir1/dir2/hello") helloMsg archive <- addFilesToArchive [OptRecursive] emptyArchive [(tmpDir ++ "/dir1")] removeDirectoryRecursive (tmpDir ++ "/dir1") extractFilesFromArchive [OptVerbose] archive hi <- BS.readFile (tmpDir ++ "/dir1/hi") hello <- BS.readFile (tmpDir ++ "/dir1/dir2/hello") assertEqual ("contents of " ++ tmpDir ++ "/dir1/hi") hiMsg hi assertEqual ("contents of " ++ tmpDir ++ "/dir1/dir2/hello") helloMsg hello #ifndef _WINDOWS testExtractFilesWithPosixAttrs :: FilePath -> Test testExtractFilesWithPosixAttrs tmpDir = TestCase $ do createDirectory (tmpDir ++ "/dir3") let hiMsg = "hello there" writeFile (tmpDir ++ "/dir3/hi") hiMsg let perms = unionFileModes ownerReadMode $ unionFileModes ownerWriteMode ownerExecuteMode setFileMode (tmpDir ++ "/dir3/hi") perms archive <- addFilesToArchive [OptRecursive] emptyArchive [(tmpDir ++ "/dir3")] removeDirectoryRecursive (tmpDir ++ "/dir3") extractFilesFromArchive [OptVerbose] archive hi <- readFile (tmpDir ++ "/dir3/hi") fm <- fmap fileMode $ getFileStatus (tmpDir ++ "/dir3/hi") assertEqual "file modes" perms (intersectFileModes perms fm) assertEqual ("contents of " ++ tmpDir ++ "/dir3/hi") hiMsg hi #endif zip-archive-0.3.1.1/LICENSE0000644000000000000000000000274213077600042013272 0ustar0000000000000000zip-archive - Haskell library Copyright (c) 2008-2012, John MacFarlane (jgm@berkeley.edu) All rights reserved. Redistribution and use in source and binary forms, with or without modification, are permitted provided that the following conditions are met: * Redistributions of source code must retain the above copyright notice, this list of conditions and the following disclaimer. * Redistributions in binary form must reproduce the above copyright notice, this list of conditions and the following disclaimer in the documentation and/or other materials provided with the distribution. * The names of its contributors may not be used to endorse or promote products derived from this software without specific prior written permission. THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT HOLDER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. zip-archive-0.3.1.1/Setup.hs0000644000000000000000000000005613114772205013720 0ustar0000000000000000import Distribution.Simple main = defaultMain zip-archive-0.3.1.1/zip-archive.cabal0000644000000000000000000000465313121700630015467 0ustar0000000000000000Name: zip-archive Version: 0.3.1.1 Cabal-Version: >= 1.10 Build-type: Simple Synopsis: Library for creating and modifying zip archives. Description: The zip-archive library provides functions for creating, modifying, and extracting files from zip archives. Category: Codec Tested-with: GHC == 7.4.2, GHC == 7.6.3, GHC == 7.8.2 License: BSD3 License-file: LICENSE Homepage: http://github.com/jgm/zip-archive Author: John MacFarlane Maintainer: jgm@berkeley.edu Extra-Source-Files: changelog, README.markdown, tests/test4.zip, tests/test4/a.txt, tests/test4/b.bin, "tests/test4/c/with spaces.txt" Source-repository head type: git location: git://github.com/jgm/zip-archive.git flag splitBase Description: Choose the new, smaller, split-up base package. Default: True flag executable Description: Build the Zip executable. Default: False Library if flag(splitBase) Build-depends: base >= 3 && < 5, pretty, containers else Build-depends: base < 3 Build-depends: binary >= 0.5, zlib, filepath, bytestring >= 0.10.0, array, mtl, text >= 0.11, old-time, digest >= 0.0.0.1, directory, time Exposed-modules: Codec.Archive.Zip Default-Language: Haskell98 Hs-Source-Dirs: src Ghc-Options: -Wall if os(windows) cpp-options: -D_WINDOWS else Build-depends: unix Executable zip-archive if flag(executable) Buildable: True else Buildable: False Main-is: Main.hs Hs-Source-Dirs: . Build-Depends: base >= 4.2 && < 5, directory >= 1.1, bytestring >= 0.9.0, zip-archive Other-Modules: Paths_zip_archive Ghc-Options: -Wall Default-Language: Haskell98 Test-Suite test-zip-archive Type: exitcode-stdio-1.0 Main-Is: test-zip-archive.hs Hs-Source-Dirs: tests Build-Depends: base >= 4.2 && < 5, directory, bytestring >= 0.9.0, process, time, old-time, HUnit, zip-archive, temporary Default-Language: Haskell98 Ghc-Options: -Wall if os(windows) cpp-options: -D_WINDOWS else Build-depends: unix zip-archive-0.3.1.1/changelog0000644000000000000000000001173213121706702014136 0ustar0000000000000000zip-archive 0.3.1.1 * readEntry: Read file as a strict ByteString. This avoids problems on Windows, where the file handle wasn't being closed. * Added appveyor.yml to do continuous testing on Windows. * Test suite: remove need for external zip program (#35). Instead of creating an archive with zip, we now store a small externally created zip archive to use for testing. zip-archive 0.3.1 * Don't use a custom build (#28). * Renamed executable Zip -> zip-archive, added --debug option. The --debug option prints the intermediate Haskell data structure. zip-archive 0.3.0.7 * Fix check for unix file attributes (#34). Previously attributes would not always be preserved for files in zip archives. zip-archive 0.3.0.6 * Bump bytestring lower bound so toStrict is guaranteed (Benjamin Landers). zip-archive 0.3.0.5 * Fix bug in `OptLocation` handling (EugeneN). When using `OptLocation folder False` (for adding files to an archive into a folder without preserving full path hierarchy), original files' names were ignored, resulting in all the files getting the same name. zip-archive 0.3.0.4 * Fix `toArchive` so it doesn't use too much memory when a data data descriptor holds the size (Michael Stahl, #29). The size fields in the local file headers may not contain valid values, in which case the sizes are stored in a "data descriptor" that follows the file data. Previously handling this case required reading the entire archive is a `[Word8]` list. With this change, `getWordsTilSig` iteratively reads chunks as strict ByteStrings and converts them to a lazy ByteString at the end. zip-archive 0.3.0.3 * Test suite: use withTempDir to create temporary directory. This should help fix problems some have encountered with the test suite leaving a temporary directory behind. zip-archive 0.3.0.2 * Fix test suite so it runs on Windows. * Zip executable: get version from cabal `Paths_zip_archive` (#27). zip-archive 0.3.0.1 * Set `eVersionMadeBy` to 0 (default) in `toEntry`, since we are setting external attributes to 0. See jgm/pandoc#2822. Only to `eVersionMadeBy` to UNIX if we actually read file attributes on a UNIX system. zip-archive 0.3 * Support preservation of file modes on Posix (Dan Aloni, #26). * Add `eVersionMadeBy` field to `Entry` (API change). * Export `ZipException` (API change). * `fromEntry` no longer checks for CRC32 match. Previously, it issued `error` if the match failed. CRC32 match is now checked in `writeEntry` instead, and a `CRC32Exception` is raised if the checksum doesn't match. * Test suite: return nonzero status if there are test failures. Previously we mistakenly did this only on 'errors', not failures. * Test suite: don't use -9 with zip as it isn't always available. * Use .travis.yml that builds on both stack and cabal. zip-archive 0.2.3.7 * Declared test suite's dependency on 'zip' using custom Setup.lhs (#21,#22). zip-archive 0.2.3.6 * Removed hard-coded path to zip in test suite (#21). * Removed misplaced build-depends in cabal file. zip-archive 0.2.3.5 * Allow compilation with binary >= 0.5. Note that toArchiveOrFail is not safe when compiled against binary < 0.7; it will never return a Left value, and will raise an error if parsing fails, just like toArchive. This is documented in the haddocks. This is ugly, but justified by the need to have a version of zip-archive that compiles against older versions of binary. zip-archive 0.2.3.4 * Make sure all path comparisons compare normalized paths. So, findEntryByPath "foo" will find something stored as "./foo" in the zip container. zip-archive 0.2.3.3 * Better normalization of file paths: "./foo/bar" and "foo/./bar" are now treated the same, for example. Note that we do not yet treat "foo/../bar" and "bar" as the same. zip-archive 0.2.3.2 * Removed lower bound on directory (>= 1.2), which caused build failures with GHC 7.4 and 7.6. * Added travis script for automatic testing on 3 GHC versions. zip-archive 0.2.3.1 * Require binary >= 0.7 and directory >= 1.2. The newer binary is needed to provide toArchiveOrFail. The other change is mainly for convenience, to avoid lots of ugly conditional compilation. zip-archive 0.2.3 * Export new function `toArchiveOrFail`. Closes #17. * Set general purpose bit flag to use UTF8 in local file header. Otherwise we get a mismatch between the flag in the central directory and the flag in the local file header, which causes some programs not to be able to extract the files. Closes #19. zip-archive 0.2.2.1 * Fix a stack overflow in getWordsTillSig (Tristan Ravitch). zip-archive 0.2.2 * Set bit 11 in the file header to ensure other programs recognize UTF-8 encoded file names (Tobias Brandt). zip-archive 0.2.1 * Added OptLocation, to specify the path to which a file is to be added when readEntry is used (Stephen McIntosh). zip-archive-0.3.1.1/README.markdown0000644000000000000000000000020613077600042014757 0ustar0000000000000000zip-archive =========== The zip-archive library provides functions for creating, modifying, and extracting files from zip archives. zip-archive-0.3.1.1/tests/test4.zip0000644000000000000000000000151213121674764015224 0ustar0000000000000000PK IJtest4/UT yGYyGYux PK IJBC test4/a.txtUT yGYyGYux Hello, this is a test! PK IJ[ test4/b.binUT yGYyGYux lѫ>0^ڪ@ PK IJtest4/c/UT yGYyGYux PK IJtest4/c/with spaces.txtUT yGYyGYux Another file. PK IJAtest4/UTyGYux PK IJBC @test4/a.txtUTyGYux PK IJ[ test4/b.binUTyGYux PK IJAtest4/c/UTyGYux PK IJ<test4/c/with spaces.txtUTyGYux PKzip-archive-0.3.1.1/tests/test4/a.txt0000644000000000000000000000002713121674637015460 0ustar0000000000000000Hello, this is a test! zip-archive-0.3.1.1/tests/test4/b.bin0000644000000000000000000000003113121674674015406 0ustar0000000000000000lѫ>0^ڪ@ zip-archive-0.3.1.1/tests/test4/c/with spaces.txt0000644000000000000000000000001613121674712017664 0ustar0000000000000000Another file.