Copyright | John MacFarlane |
---|---|
License | BSD3 |
Maintainer | John MacFarlane < jgm at berkeley dot edu > |
Stability | unstable |
Portability | so far only tested on GHC |
Safe Haskell | Safe-Inferred |
Language | Haskell98 |
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 strong 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 http://www.pkware.com/documents/casestudies/APPNOTE.TXT
Synopsis
- data Archive = Archive {
- zEntries :: [Entry]
- zSignature :: Maybe ByteString
- zComment :: !ByteString
- data Entry = Entry {
- eRelativePath :: FilePath
- eCompressionMethod :: !CompressionMethod
- eEncryptionMethod :: !EncryptionMethod
- eLastModified :: !Integer
- eCRC32 :: !Word32
- eCompressedSize :: !Word32
- eUncompressedSize :: !Word32
- eExtraField :: !ByteString
- eFileComment :: !ByteString
- eVersionMadeBy :: !Word16
- eInternalFileAttributes :: !Word16
- eExternalFileAttributes :: !Word32
- eCompressedData :: !ByteString
- data CompressionMethod
- data EncryptionMethod
- data ZipOption
- data ZipException
- emptyArchive :: Archive
- toArchive :: ByteString -> Archive
- toArchiveOrFail :: ByteString -> Either String Archive
- fromArchive :: Archive -> ByteString
- filesInArchive :: Archive -> [FilePath]
- addEntryToArchive :: Entry -> Archive -> Archive
- deleteEntryFromArchive :: FilePath -> Archive -> Archive
- findEntryByPath :: FilePath -> Archive -> Maybe Entry
- fromEntry :: Entry -> ByteString
- fromEncryptedEntry :: String -> Entry -> Maybe ByteString
- isEncryptedEntry :: Entry -> Bool
- toEntry :: FilePath -> Integer -> ByteString -> Entry
- isEntrySymbolicLink :: Entry -> Bool
- symbolicLinkEntryTarget :: Entry -> Maybe FilePath
- entryCMode :: Entry -> CMode
- readEntry :: [ZipOption] -> FilePath -> IO Entry
- writeEntry :: [ZipOption] -> Entry -> IO ()
- writeSymbolicLinkEntry :: [ZipOption] -> Entry -> IO ()
- addFilesToArchive :: [ZipOption] -> Archive -> [FilePath] -> IO Archive
- extractFilesFromArchive :: [ZipOption] -> Archive -> IO ()
Data structures
Structured representation of a zip archive, including directory information and contents (in lazy bytestrings).
Archive | |
|
Representation of an archived file, including content and metadata.
Entry | |
|
data CompressionMethod Source #
Compression methods.
Instances
Read CompressionMethod Source # | |
Defined in Codec.Archive.Zip | |
Show CompressionMethod Source # | |
Defined in Codec.Archive.Zip showsPrec :: Int -> CompressionMethod -> ShowS # show :: CompressionMethod -> String # showList :: [CompressionMethod] -> ShowS # | |
Eq CompressionMethod Source # | |
Defined in Codec.Archive.Zip (==) :: CompressionMethod -> CompressionMethod -> Bool # (/=) :: CompressionMethod -> CompressionMethod -> Bool # |
data EncryptionMethod Source #
NoEncryption | Entry is not encrypted |
PKWAREEncryption !Word8 | Entry is encrypted with the traditional PKWARE encryption |
Instances
Read EncryptionMethod Source # | |
Defined in Codec.Archive.Zip | |
Show EncryptionMethod Source # | |
Defined in Codec.Archive.Zip showsPrec :: Int -> EncryptionMethod -> ShowS # show :: EncryptionMethod -> String # showList :: [EncryptionMethod] -> ShowS # | |
Eq EncryptionMethod Source # | |
Defined in Codec.Archive.Zip (==) :: EncryptionMethod -> EncryptionMethod -> Bool # (/=) :: EncryptionMethod -> EncryptionMethod -> Bool # |
Options for addFilesToArchive
and extractFilesFromArchive
.
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 |
OptPreserveSymbolicLinks | Preserve symbolic links as such. This option is ignored on Windows. |
data ZipException Source #
Instances
Data ZipException Source # | |
Defined in Codec.Archive.Zip gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ZipException -> c ZipException # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ZipException # toConstr :: ZipException -> Constr # dataTypeOf :: ZipException -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ZipException) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ZipException) # gmapT :: (forall b. Data b => b -> b) -> ZipException -> ZipException # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ZipException -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ZipException -> r # gmapQ :: (forall d. Data d => d -> u) -> ZipException -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ZipException -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ZipException -> m ZipException # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ZipException -> m ZipException # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ZipException -> m ZipException # | |
Exception ZipException Source # | |
Defined in Codec.Archive.Zip | |
Show ZipException Source # | |
Defined in Codec.Archive.Zip showsPrec :: Int -> ZipException -> ShowS # show :: ZipException -> String # showList :: [ZipException] -> ShowS # | |
Eq ZipException Source # | |
Defined in Codec.Archive.Zip (==) :: ZipException -> ZipException -> Bool # (/=) :: ZipException -> ZipException -> Bool # |
emptyArchive :: Archive Source #
A zip archive with no contents.
Pure functions for working with zip archives
toArchive :: ByteString -> Archive Source #
Reads an Archive
structure from a raw zip archive (in a lazy bytestring).
fromArchive :: Archive -> ByteString Source #
Writes an Archive
structure to a raw zip archive (in a lazy bytestring).
filesInArchive :: Archive -> [FilePath] Source #
Returns a list of files in a zip archive.
addEntryToArchive :: Entry -> Archive -> Archive Source #
Adds an entry to a zip archive, or updates an existing entry.
deleteEntryFromArchive :: FilePath -> Archive -> Archive Source #
Deletes an entry from a zip archive.
findEntryByPath :: FilePath -> Archive -> Maybe Entry Source #
Returns Just the zip entry with the specified path, or Nothing.
fromEntry :: Entry -> ByteString Source #
Returns uncompressed contents of zip entry.
fromEncryptedEntry :: String -> Entry -> Maybe ByteString Source #
Returns decrypted and uncompressed contents of zip entry.
:: FilePath | File path for entry |
-> Integer | Modification time for entry (seconds since unix epoch) |
-> ByteString | Contents of entry |
-> Entry |
Create an Entry
with specified file path, modification time, and contents.
entryCMode :: Entry -> CMode Source #
Get the eExternalFileAttributes
of an Entry
as a CMode
a.k.a. FileMode
IO functions for working with zip archives
readEntry :: [ZipOption] -> FilePath -> IO Entry Source #
Generates a Entry
from a file or directory.
writeEntry :: [ZipOption] -> Entry -> IO () Source #
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.
writeSymbolicLinkEntry :: [ZipOption] -> Entry -> IO () Source #
Write an Entry
representing a symbolic link to a file.
If the Entry
does not represent a symbolic link or
the options do not contain OptPreserveSymbolicLinks
, this
function behaves like writeEntry
.
addFilesToArchive :: [ZipOption] -> Archive -> [FilePath] -> IO Archive Source #
Add the specified files to an Archive
. If OptRecursive
is specified,
recursively add files contained in directories. if OptPreserveSymbolicLinks
is specified, don't recurse into it. If OptVerbose
is specified,
print messages to stderr.
extractFilesFromArchive :: [ZipOption] -> Archive -> IO () Source #
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.
This function fails if encrypted entries are present