Copyright | © 2016 Mark Karpov |
---|---|
License | BSD 3 clause |
Maintainer | Mark Karpov <markkarpov@openmailbox.org> |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
The module provides everything you need to manipulate Zip archives. There are three things that should be clarified right away, to avoid confusion in the future.
First, we use EntrySelector
type that can be obtained from Path
Rel
File
paths. This method may seem awkward at first, but it will protect
you from problems with portability when your archive is unpacked on a
different platform. Using of well-typed paths is also something you
should consider doing in your projects anyway. Even if you don't want to
use Path module in your project, it's easy to marshal FilePath
to
Path
just before using functions from the library.
The second thing, that is rather a consequence of the first, is that there is no way to add directories, or to be precise, empty directories to your archive. This approach is used in Git, and I find it quite sane.
Finally, the third feature of the library is that it does not modify
archive instantly, because doing so on every manipulation would often be
inefficient. Instead we maintain collection of pending actions that can
be turned into optimized procedure that efficiently modifies archive in
one pass. Normally this should be of no concern to you, because all
actions are performed automatically when you leave the realm of
ZipArchive
monad. If, however, you ever need to force update, commit
function is your friend. There are even “undo” functions, by the way.
An example of a program that prints list of archive entries:
import Codec.Archive.Zip import Path.IO (resolveFile') import System.Environment (getArgs) import qualified Data.Map as M main :: IO () main = do [fp] <- getArgs path <- resolveFile' fp entries <- withArchive path (M.keys <$> getEntries) mapM_ print entries
Create a Zip archive with a Hello World file:
import Codec.Archive.Zip import Path (parseRelFile) import Path.IO (resolveFile') import System.Environment (getArgs) main :: IO () main = do [fp] <- getArgs path <- resolveFile' fp s <- parseRelFile "hello-world.txt" >>= mkEntrySelector createArchive path (addEntry Store "Hello, World!" s)
Extract contents of specific file and print it:
import Codec.Archive.Zip import Path (parseRelFile) import Path.IO (resolveFile') import System.Environment (getArgs) import qualified Data.ByteString.Char8 as B main :: IO () main = do [fp,f] <- getArgs path <- resolveFile' fp s <- parseRelFile f >>= mkEntrySelector bs <- withArchive path (getEntry s) B.putStrLn bs
- data EntrySelector
- mkEntrySelector :: MonadThrow m => Path Rel File -> m EntrySelector
- unEntrySelector :: EntrySelector -> Path Rel File
- getEntryName :: EntrySelector -> Text
- data EntrySelectorException = InvalidEntrySelector (Path Rel File)
- data EntryDescription = EntryDescription {}
- data CompressionMethod
- data ArchiveDescription = ArchiveDescription {}
- data ZipException
- data ZipArchive a
- createArchive :: (MonadIO m, MonadCatch m) => Path b File -> ZipArchive a -> m a
- withArchive :: (MonadIO m, MonadThrow m) => Path b File -> ZipArchive a -> m a
- getEntries :: ZipArchive (Map EntrySelector EntryDescription)
- doesEntryExist :: EntrySelector -> ZipArchive Bool
- getEntryDesc :: EntrySelector -> ZipArchive (Maybe EntryDescription)
- getEntry :: EntrySelector -> ZipArchive ByteString
- getEntrySource :: EntrySelector -> ZipArchive (Source (ResourceT IO) ByteString)
- sourceEntry :: EntrySelector -> Sink ByteString (ResourceT IO) a -> ZipArchive a
- saveEntry :: EntrySelector -> Path b File -> ZipArchive ()
- checkEntry :: EntrySelector -> ZipArchive Bool
- unpackInto :: Path b Dir -> ZipArchive ()
- getArchiveComment :: ZipArchive (Maybe Text)
- getArchiveDescription :: ZipArchive ArchiveDescription
- addEntry :: CompressionMethod -> ByteString -> EntrySelector -> ZipArchive ()
- sinkEntry :: CompressionMethod -> Source (ResourceT IO) ByteString -> EntrySelector -> ZipArchive ()
- loadEntry :: CompressionMethod -> (Path Abs File -> ZipArchive EntrySelector) -> Path b File -> ZipArchive ()
- copyEntry :: Path b File -> EntrySelector -> EntrySelector -> ZipArchive ()
- packDirRecur :: CompressionMethod -> (Path Abs File -> ZipArchive EntrySelector) -> Path b Dir -> ZipArchive ()
- renameEntry :: EntrySelector -> EntrySelector -> ZipArchive ()
- deleteEntry :: EntrySelector -> ZipArchive ()
- recompress :: CompressionMethod -> EntrySelector -> ZipArchive ()
- setEntryComment :: Text -> EntrySelector -> ZipArchive ()
- deleteEntryComment :: EntrySelector -> ZipArchive ()
- setModTime :: UTCTime -> EntrySelector -> ZipArchive ()
- addExtraField :: Word16 -> ByteString -> EntrySelector -> ZipArchive ()
- deleteExtraField :: Word16 -> EntrySelector -> ZipArchive ()
- forEntries :: (EntrySelector -> ZipArchive ()) -> ZipArchive ()
- setArchiveComment :: Text -> ZipArchive ()
- deleteArchiveComment :: ZipArchive ()
- undoEntryChanges :: EntrySelector -> ZipArchive ()
- undoArchiveChanges :: ZipArchive ()
- undoAll :: ZipArchive ()
- commit :: ZipArchive ()
Types
Entry selector
data EntrySelector Source #
This data type serves for naming and selection of archive
entries. It can be created only with help of smart constructor
mkEntrySelector
, and it's the only “key” that can be used to select
files in archive or to name new files.
The abstraction is crucial for ensuring that created archives are portable across operating systems, file systems, and different platforms. Since on some operating systems, file paths are case-insensitive, this selector is also case-insensitive. It makes sure that only relative paths are used to name files inside archive, as it's recommended in the specification. It also guarantees that forward slashes are used when the path is stored inside archive for compatibility with Unix-like operating systems (as it is recommended in the specification). On the other hand, in can be rendered as ordinary relative file path in OS-specific format, when needed.
mkEntrySelector :: MonadThrow m => Path Rel File -> m EntrySelector Source #
Create EntrySelector
from Path Rel File
. To avoid problems with
distribution of the archive, characters that some operating systems do
not expect in paths are not allowed. Proper paths should pass these
checks:
This function can throw EntrySelectorException
exception.
unEntrySelector :: EntrySelector -> Path Rel File Source #
Make a relative path from EntrySelector
. Every EntrySelector
produces single Path Rel File
that corresponds to it.
getEntryName :: EntrySelector -> Text Source #
Get entry name given EntrySelector
in from that is suitable for
writing to file header.
data EntrySelectorException Source #
Exception describing various troubles you can have with
EntrySelector
.
InvalidEntrySelector (Path Rel File) | Selector cannot be created from this path |
Entry description
data EntryDescription Source #
This record represents all information about archive entry that can be stored in a .ZIP archive. It does not mirror local file header or central directory file header, but their binary representation can be built given this date structure and actual archive contents.
EntryDescription | |
|
data CompressionMethod Source #
Supported compression methods.
Archive description
Exceptions
data ZipException Source #
Bad things that can happen when you use the library.
EntryDoesNotExist (Path Abs File) EntrySelector | Thrown when you try to get contents of non-existing entry |
ParsingFailed (Path Abs File) String | Thrown when archive structure cannot be parsed |
Archive monad
data ZipArchive a Source #
Monad that provides context necessary for performing operations on archives. It's intentionally opaque and not a monad transformer to limit number of actions that can be performed in it to those provided by this module and their combinations.
:: (MonadIO m, MonadCatch m) | |
=> Path b File | Location of archive file to create |
-> ZipArchive a | Actions that form archive's content |
-> m a |
Create new archive given its location and action that describes how to
create content in the archive. This will silently overwrite specified
file if it already exists. See withArchive
if you want to work with
existing archive.
:: (MonadIO m, MonadThrow m) | |
=> Path b File | Location of archive to work with |
-> ZipArchive a | Actions on that archive |
-> m a |
Work with an existing archive. See createArchive
if you want to
create new archive instead.
This operation may fail with:
isAlreadyInUseError
if the file is already open and cannot be reopened;isDoesNotExistError
if the file does not exist;isPermissionError
if the user does not have permission to open the file;ParsingFailed
when specified archive is something this library cannot parse (this includes multi-disk archives, for example).
Please note that entries with invalid (non-portable) file names may be
missing in list of entries. Files that are compressed with unsupported
compression methods are skipped as well. Also, if several entries would
collide on some operating systems (such as Windows, because of its
case-insensitivity), only one of them will be available, because
EntrySelector
is case-insensitive. These are consequences of the design
decision to make it impossible to create non-portable archives with this
library.
Retrieving information
getEntries :: ZipArchive (Map EntrySelector EntryDescription) Source #
Retrieve description of all archive entries. This is an efficient operation that can be used for example to list all entries in archive. Do not hesitate to use the function frequently: scanning of archive happens only once anyway.
Please note that returned value only reflects actual contents of archive
in file system, non-committed actions cannot influence list of entries,
see commit
for more information.
doesEntryExist :: EntrySelector -> ZipArchive Bool Source #
Check whether specified entry exists in the archive. This is a simple shortcut defined as:
doesEntryExist s = M.member s <$> getEntries
getEntryDesc :: EntrySelector -> ZipArchive (Maybe EntryDescription) Source #
Get EntryDescription
for specified entry. This is a simple shortcut
defined as:
getEntryDesc s = M.lookup s <$> getEntries
:: EntrySelector | Selector that identifies archive entry |
-> ZipArchive ByteString | Contents of the entry |
Get contents of specific archive entry as strict ByteString
. It's not
recommended to use this on big entries, because it will suck out a lot of
memory. For big entries, use conduits: sourceEntry
.
Throws: EntryDoesNotExist
.
getEntrySource :: EntrySelector -> ZipArchive (Source (ResourceT IO) ByteString) Source #
:: EntrySelector | Selector that identifies archive entry |
-> Sink ByteString (ResourceT IO) a | Sink where to stream entry contents |
-> ZipArchive a | Contents of the entry (if found) |
Stream contents of archive entry to specified Sink
.
Throws: EntryDoesNotExist
.
:: EntrySelector | Selector that identifies archive entry |
-> Path b File | Where to save the file |
-> ZipArchive () |
Save specific archive entry as a file in the file system.
Throws: EntryDoesNotExist
.
:: EntrySelector | Selector that identifies archive entry |
-> ZipArchive Bool | Is the entry intact? |
Calculate CRC32 check sum and compare it with value read from
archive. The function returns True
when the check sums are the same —
that is, data is not corrupted.
Throws: EntryDoesNotExist
.
unpackInto :: Path b Dir -> ZipArchive () Source #
Unpack entire archive into specified directory. The directory will be created if it does not exist.
getArchiveComment :: ZipArchive (Maybe Text) Source #
Get archive comment.
getArchiveDescription :: ZipArchive ArchiveDescription Source #
Get archive description record.
Modifying archive
Adding entries
:: CompressionMethod | Compression method to use |
-> ByteString | Entry contents |
-> EntrySelector | Name of entry to add |
-> ZipArchive () |
Add a new entry to archive given its contents in binary form.
:: CompressionMethod | Compression method to use |
-> Source (ResourceT IO) ByteString | Source of entry contents |
-> EntrySelector | Name of entry to add |
-> ZipArchive () |
Stream data from the specified source to an archive entry.
:: CompressionMethod | Compression method to use |
-> (Path Abs File -> ZipArchive EntrySelector) | How to get |
-> Path b File | Path to file to add |
-> ZipArchive () |
Load entry from given file.
:: Path b File | Path to archive to copy from |
-> EntrySelector | Name of entry (in source archive) to copy |
-> EntrySelector | Name of entry to insert (in actual archive) |
-> ZipArchive () |
Copy entry “as is” from another .ZIP archive. If the entry does not
exists in that archive, EntryDoesNotExist
will be eventually thrown.
:: CompressionMethod | Compression method to use |
-> (Path Abs File -> ZipArchive EntrySelector) | How to get |
-> Path b Dir | Path to directory to add |
-> ZipArchive () |
Add entire directory to archive. Please note that due to design of the library, empty sub-directories won't be added.
The action can throw the same exceptions as listDirRecur
and
InvalidEntrySelector
.
Modifying entries
:: EntrySelector | Original entry name |
-> EntrySelector | New entry name |
-> ZipArchive () |
Rename entry in archive. If the entry does not exist, nothing will happen.
deleteEntry :: EntrySelector -> ZipArchive () Source #
Delete entry from archive, if it does not exist, nothing will happen.
:: CompressionMethod | New compression method |
-> EntrySelector | Name of entry to re-compress |
-> ZipArchive () |
Change compression method of an entry, if it does not exist, nothing will happen.
:: Text | Text of the comment |
-> EntrySelector | Name of entry to comment upon |
-> ZipArchive () |
Set entry comment, if that entry does not exist, nothing will happen. Note that if binary representation of comment is longer than 65535 bytes, it will be truncated on writing.
deleteEntryComment :: EntrySelector -> ZipArchive () Source #
Delete entry's comment, if that entry does not exist, nothing will happen.
:: UTCTime | New modification time |
-> EntrySelector | Name of entry to modify |
-> ZipArchive () |
Set “last modification” date/time. Specified entry may be missing, in that case this action has no effect.
:: Word16 | Tag (header id) of extra field to add |
-> ByteString | Body of the field |
-> EntrySelector | Name of entry to modify |
-> ZipArchive () |
Add an extra field. Specified entry may be missing, in that case this action has no effect.
:: Word16 | Tag (header id) of extra field to delete |
-> EntrySelector | Name of entry to modify |
-> ZipArchive () |
Delete an extra field by its type (tag). Specified entry may be missing, in that case this action has no effect.
:: (EntrySelector -> ZipArchive ()) | Action to perform |
-> ZipArchive () |
Perform an action on every entry in archive.
Operations on archive as a whole
setArchiveComment :: Text -> ZipArchive () Source #
Set comment of entire archive.
deleteArchiveComment :: ZipArchive () Source #
Delete archive comment if it's present.
Control over editing
undoEntryChanges :: EntrySelector -> ZipArchive () Source #
Undo changes to specific archive entry.
undoArchiveChanges :: ZipArchive () Source #
Undo changes to archive as a whole (archive's comment).
undoAll :: ZipArchive () Source #
Undo all changes made in this editing session.
commit :: ZipArchive () Source #
Archive contents are not modified instantly, but instead changes are
collected as “pending actions” that should be committed in order to
efficiently modify archive in one pass. The actions are committed
automatically when program leaves the realm of ZipArchive
monad
(i.e. as part of createArchive
or withArchive
), or can be forced
explicitly with help of this function. Once committed, changes take place
in the file system and cannot be undone.