zip-1.7.1: Operations on zip archives
Copyright© 2016–present Mark Karpov
LicenseBSD 3 clause
MaintainerMark Karpov <markkarpov92@gmail.com>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Codec.Archive.Zip

Description

The module provides everything you may need to manipulate Zip archives. There are three things that should be clarified right away, to avoid confusion.

First, we use the EntrySelector type that can be obtained from relative FilePaths (paths to directories are not allowed). This method may seem awkward at first, but it will protect you from the problems with portability when your archive is unpacked on a different platform.

Second, 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 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 a collection of pending actions that can be turned into an optimized procedure that efficiently modifies the archive in one pass. Normally, this should be of no concern to you, because all actions are performed automatically when you leave the ZipArchive monad. If, however, you ever need to force an update, the commit function is your friend.

Examples

An example of a program that prints a list of archive entries:

import Codec.Archive.Zip
import System.Environment (getArgs)
import qualified Data.Map as M

main :: IO ()
main = do
  [path]  <- getArgs
  entries <- withArchive path (M.keys <$> getEntries)
  mapM_ print entries

Create a Zip archive with a “Hello World” file:

import Codec.Archive.Zip
import System.Environment (getArgs)

main :: IO ()
main = do
  [path] <- getArgs
  s      <- mkEntrySelector "hello-world.txt"
  createArchive path (addEntry Store "Hello, World!" s)

Extract contents of a file and print them:

import Codec.Archive.Zip
import System.Environment (getArgs)
import qualified Data.ByteString.Char8 as B

main :: IO ()
main = do
  [path,f] <- getArgs
  s        <- mkEntrySelector f
  bs       <- withArchive path (getEntry s)
  B.putStrLn bs
Synopsis

Types

Entry selector

data EntrySelector Source #

This data type serves for naming and selection of archive entries. It can be created only with the help of the smart constructor mkEntrySelector, and it's the only “key” that can be used to refer to files in the archive or to name new archive entries.

The abstraction is crucial for ensuring that created archives are portable across operating systems, file systems, and 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 the archive for compatibility with Unix-like operating systems (as recommended in the specification). On the other hand, in can be rendered as an ordinary relative file path in OS-specific format when needed.

mkEntrySelector :: MonadThrow m => FilePath -> m EntrySelector Source #

Create an EntrySelector from a FilePath. To avoid problems with distribution of the archive, characters that some operating systems do not expect in paths are not allowed.

Argument to mkEntrySelector should pass these checks:

  • isValid
  • isValid
  • it is a relative path without slash at the end
  • binary representations of normalized path should be not longer than 65535 bytes

This function can throw an EntrySelectorException.

unEntrySelector :: EntrySelector -> FilePath Source #

Restore a relative path from EntrySelector. Every EntrySelector corresponds to a FilePath.

getEntryName :: EntrySelector -> Text Source #

Get an entry name in the from that is suitable for writing to file header, given an EntrySelector.

newtype EntrySelectorException Source #

The problems you can have with an EntrySelector.

Constructors

InvalidEntrySelector FilePath

EntrySelector cannot be created from this path

Entry description

data EntryDescription Source #

The 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 representations can be built given this data structure and the archive contents.

Constructors

EntryDescription 

Fields

Instances

Instances details
Eq EntryDescription Source # 
Instance details

Defined in Codec.Archive.Zip.Type

data CompressionMethod Source #

The supported compression methods.

Constructors

Store

Store file uncompressed

Deflate

Deflate

BZip2

Compressed using BZip2 algorithm

Zstd

Compressed using Zstandard algorithm

Since: 1.6.0

Instances

Instances details
Bounded CompressionMethod Source # 
Instance details

Defined in Codec.Archive.Zip.Type

Enum CompressionMethod Source # 
Instance details

Defined in Codec.Archive.Zip.Type

Eq CompressionMethod Source # 
Instance details

Defined in Codec.Archive.Zip.Type

Data CompressionMethod Source # 
Instance details

Defined in Codec.Archive.Zip.Type

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CompressionMethod -> c CompressionMethod #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CompressionMethod #

toConstr :: CompressionMethod -> Constr #

dataTypeOf :: CompressionMethod -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CompressionMethod) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CompressionMethod) #

gmapT :: (forall b. Data b => b -> b) -> CompressionMethod -> CompressionMethod #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CompressionMethod -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CompressionMethod -> r #

gmapQ :: (forall d. Data d => d -> u) -> CompressionMethod -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CompressionMethod -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CompressionMethod -> m CompressionMethod #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CompressionMethod -> m CompressionMethod #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CompressionMethod -> m CompressionMethod #

Ord CompressionMethod Source # 
Instance details

Defined in Codec.Archive.Zip.Type

Read CompressionMethod Source # 
Instance details

Defined in Codec.Archive.Zip.Type

Show CompressionMethod Source # 
Instance details

Defined in Codec.Archive.Zip.Type

Archive description

data ArchiveDescription Source #

The information about the archive as a whole.

Constructors

ArchiveDescription 

Fields

Instances

Instances details
Eq ArchiveDescription Source # 
Instance details

Defined in Codec.Archive.Zip.Type

Data ArchiveDescription Source # 
Instance details

Defined in Codec.Archive.Zip.Type

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ArchiveDescription -> c ArchiveDescription #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ArchiveDescription #

toConstr :: ArchiveDescription -> Constr #

dataTypeOf :: ArchiveDescription -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ArchiveDescription) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ArchiveDescription) #

gmapT :: (forall b. Data b => b -> b) -> ArchiveDescription -> ArchiveDescription #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ArchiveDescription -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ArchiveDescription -> r #

gmapQ :: (forall d. Data d => d -> u) -> ArchiveDescription -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ArchiveDescription -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ArchiveDescription -> m ArchiveDescription #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ArchiveDescription -> m ArchiveDescription #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ArchiveDescription -> m ArchiveDescription #

Ord ArchiveDescription Source # 
Instance details

Defined in Codec.Archive.Zip.Type

Read ArchiveDescription Source # 
Instance details

Defined in Codec.Archive.Zip.Type

Show ArchiveDescription Source # 
Instance details

Defined in Codec.Archive.Zip.Type

Exceptions

data ZipException Source #

The bad things that can happen when you use the library.

Constructors

EntryDoesNotExist FilePath EntrySelector

Thrown when you try to get contents of non-existing entry

ParsingFailed FilePath String

Thrown when archive structure cannot be parsed.

Archive monad

data ZipArchive a Source #

Monad that provides context necessary for performing operations on zip archives. It's intentionally opaque and not a monad transformer to limit the actions that can be performed in it to those provided by this module and their combinations.

Instances

Instances details
Monad ZipArchive Source # 
Instance details

Defined in Codec.Archive.Zip

Methods

(>>=) :: ZipArchive a -> (a -> ZipArchive b) -> ZipArchive b #

(>>) :: ZipArchive a -> ZipArchive b -> ZipArchive b #

return :: a -> ZipArchive a #

Functor ZipArchive Source # 
Instance details

Defined in Codec.Archive.Zip

Methods

fmap :: (a -> b) -> ZipArchive a -> ZipArchive b #

(<$) :: a -> ZipArchive b -> ZipArchive a #

Applicative ZipArchive Source # 
Instance details

Defined in Codec.Archive.Zip

Methods

pure :: a -> ZipArchive a #

(<*>) :: ZipArchive (a -> b) -> ZipArchive a -> ZipArchive b #

liftA2 :: (a -> b -> c) -> ZipArchive a -> ZipArchive b -> ZipArchive c #

(*>) :: ZipArchive a -> ZipArchive b -> ZipArchive b #

(<*) :: ZipArchive a -> ZipArchive b -> ZipArchive a #

MonadIO ZipArchive Source # 
Instance details

Defined in Codec.Archive.Zip

Methods

liftIO :: IO a -> ZipArchive a #

MonadThrow ZipArchive Source # 
Instance details

Defined in Codec.Archive.Zip

Methods

throwM :: Exception e => e -> ZipArchive a #

MonadCatch ZipArchive Source # 
Instance details

Defined in Codec.Archive.Zip

Methods

catch :: Exception e => ZipArchive a -> (e -> ZipArchive a) -> ZipArchive a #

MonadMask ZipArchive Source # 
Instance details

Defined in Codec.Archive.Zip

Methods

mask :: ((forall a. ZipArchive a -> ZipArchive a) -> ZipArchive b) -> ZipArchive b #

uninterruptibleMask :: ((forall a. ZipArchive a -> ZipArchive a) -> ZipArchive b) -> ZipArchive b #

generalBracket :: ZipArchive a -> (a -> ExitCase b -> ZipArchive c) -> (a -> ZipArchive b) -> ZipArchive (b, c) #

MonadBase IO ZipArchive Source #

Since: 0.2.0

Instance details

Defined in Codec.Archive.Zip

Methods

liftBase :: IO α -> ZipArchive α

MonadBaseControl IO ZipArchive Source #

Since: 0.2.0

Instance details

Defined in Codec.Archive.Zip

Associated Types

type StM ZipArchive a

Methods

liftBaseWith :: (RunInBase ZipArchive IO -> IO a) -> ZipArchive a

restoreM :: StM ZipArchive a -> ZipArchive a

type StM ZipArchive a Source # 
Instance details

Defined in Codec.Archive.Zip

type StM ZipArchive a = (a, ZipState)

data ZipState Source #

The internal state record used by the ZipArchive monad. This is only exported for use with MonadBaseControl methods, you can't look inside.

Since: 0.2.0

createArchive Source #

Arguments

:: MonadIO m 
=> FilePath

Location of the archive file to create

-> ZipArchive a

Actions that create the archive's content

-> m a 

Create a new archive given its location and an action that describes how to create contents of the archive. This will silently overwrite the specified file if it already exists. See withArchive if you want to work with an existing archive.

withArchive Source #

Arguments

:: MonadIO m 
=> FilePath

Location of the archive to work with

-> ZipArchive a

Actions on that archive

-> m a 

Work with an existing archive. See createArchive if you want to create a 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 the 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 the 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 a description of all archive entries. This is an efficient operation that can be used for example to list all entries in the archive. Do not hesitate to use the function frequently: scanning of the archive happens only once.

Please note that the returned value only reflects the current contents of the archive in file system, non-committed actions are not reflected, see commit for more information.

doesEntryExist :: EntrySelector -> ZipArchive Bool Source #

Check whether the 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 a specified entry. This is a simple shortcut defined as:

getEntryDesc s = M.lookup s <$> getEntries

getEntry Source #

Arguments

:: EntrySelector

Selector that identifies archive entry

-> ZipArchive ByteString

Contents of the entry

Get contents of a specific archive entry as a 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 Source #

Arguments

:: (PrimMonad m, MonadThrow m, MonadResource m) 
=> EntrySelector

Selector that identifies archive entry

-> ZipArchive (ConduitT () ByteString m ()) 

Get an entry source.

Throws: EntryDoesNotExist.

Since: 0.1.3

sourceEntry Source #

Arguments

:: EntrySelector

Selector that identifies the archive entry

-> ConduitT ByteString Void (ResourceT IO) a

Sink where to stream entry contents

-> ZipArchive a

Contents of the entry (if found)

Stream contents of an archive entry to the given Sink.

Throws: EntryDoesNotExist.

saveEntry Source #

Arguments

:: EntrySelector

Selector that identifies the archive entry

-> FilePath

Where to save the file

-> ZipArchive () 

Save a specific archive entry as a file in the file system.

Throws: EntryDoesNotExist.

checkEntry Source #

Arguments

:: EntrySelector

Selector that identifies the archive entry

-> ZipArchive Bool

Is the entry intact?

Calculate CRC32 check sum and compare it with the value read from the archive. The function returns True when the check sums are the same—that is, the data is not corrupted.

Throws: EntryDoesNotExist.

unpackInto :: FilePath -> ZipArchive () Source #

Unpack the archive into the specified directory. The directory will be created if it does not exist.

getArchiveComment :: ZipArchive (Maybe Text) Source #

Get the archive comment.

getArchiveDescription :: ZipArchive ArchiveDescription Source #

Get the archive description record.

Modifying archive

Adding entries

addEntry Source #

Arguments

:: CompressionMethod

The compression method to use

-> ByteString

Entry contents

-> EntrySelector

Name of the entry to add

-> ZipArchive () 

Add a new entry to the archive given its contents in binary form.

sinkEntry Source #

Arguments

:: CompressionMethod

The compression method to use

-> ConduitT () ByteString (ResourceT IO) ()

Source of entry contents

-> EntrySelector

Name of the entry to add

-> ZipArchive () 

Stream data from the specified source to an archive entry.

loadEntry Source #

Arguments

:: CompressionMethod

The compression method to use

-> EntrySelector

Name of the entry to add

-> FilePath

Path to the file to add

-> ZipArchive () 

Load an entry from a given file.

copyEntry Source #

Arguments

:: FilePath

Path to the archive to copy from

-> EntrySelector

Name of the entry (in the source archive) to copy

-> EntrySelector

Name of the entry to insert (in current archive)

-> ZipArchive () 

Copy an entry “as is” from another zip archive. If the entry does not exist in that archive, EntryDoesNotExist will be thrown.

packDirRecur Source #

Arguments

:: CompressionMethod

The compression method to use

-> (FilePath -> ZipArchive EntrySelector)

How to get the EntrySelector from a path relative to the root of the directory we pack

-> FilePath

Path to the directory to add

-> ZipArchive () 

Add an directory to the archive. Please note that due to the design of the library, empty sub-directories will not be added.

The action can throw InvalidEntrySelector.

packDirRecur' Source #

Arguments

:: CompressionMethod

The compression method to use

-> (FilePath -> ZipArchive EntrySelector)

How to get the EntrySelector from a path relative to the root of the directory we pack

-> (EntrySelector -> ZipArchive ())

How to modify an entry after creation

-> FilePath

Path to the directory to add

-> ZipArchive () 

The same as packDirRecur but allows us to perform modifying actions on the created entities as we go.

Since: 1.5.0

Modifying entries

renameEntry Source #

Arguments

:: EntrySelector

The original entry name

-> EntrySelector

The new entry name

-> ZipArchive () 

Rename an entry in the archive. If the entry does not exist, nothing will happen.

deleteEntry :: EntrySelector -> ZipArchive () Source #

Delete an entry from the archive, if it does not exist, nothing will happen.

recompress Source #

Arguments

:: CompressionMethod

The new compression method

-> EntrySelector

Name of the entry to re-compress

-> ZipArchive () 

Change compression method of an entry, if it does not exist, nothing will happen.

setEntryComment Source #

Arguments

:: Text

Text of the comment

-> EntrySelector

Name of the entry to comment on

-> ZipArchive () 

Set an entry comment, if that entry does not exist, nothing will happen. Note that if binary representation of the comment is longer than 65535 bytes, it will be truncated on writing.

deleteEntryComment :: EntrySelector -> ZipArchive () Source #

Delete an entry's comment, if that entry does not exist, nothing will happen.

setModTime Source #

Arguments

:: UTCTime

New modification time

-> EntrySelector

Name of the entry to modify

-> ZipArchive () 

Set the last modification date/time. The specified entry may be missing, in that case the action has no effect.

addExtraField Source #

Arguments

:: Word16

Tag (header id) of the extra field to add

-> ByteString

Body of the field

-> EntrySelector

Name of the entry to modify

-> ZipArchive () 

Add an extra field. The specified entry may be missing, in that case this action has no effect.

deleteExtraField Source #

Arguments

:: Word16

Tag (header id) of the extra field to delete

-> EntrySelector

Name of the entry to modify

-> ZipArchive () 

Delete an extra field by its type (tag). The specified entry may be missing, in that case this action has no effect.

setExternalFileAttrs Source #

Arguments

:: Word32

External file attributes

-> EntrySelector

Name of the entry to modify

-> ZipArchive () 

Set external file attributes. This function can be used to set file permissions.

See also: Codec.Archive.Zip.Unix.

Since: 1.2.0

forEntries Source #

Arguments

:: (EntrySelector -> ZipArchive ())

The action to perform

-> ZipArchive () 

Perform an action on every entry in the archive.

Operations on archive as a whole

setArchiveComment :: Text -> ZipArchive () Source #

Set the comment of the entire archive.

deleteArchiveComment :: ZipArchive () Source #

Delete the archive's comment if it's present.

Control over editing

undoEntryChanges :: EntrySelector -> ZipArchive () Source #

Undo the changes to a specific archive entry.

undoArchiveChanges :: ZipArchive () Source #

Undo the changes to the 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 the archive in one pass. The actions are committed automatically when the program leaves the ZipArchive monad (i.e. as part of createArchive or withArchive), or can be forced explicitly with the help of this function. Once committed, changes take place in the file system and cannot be undone.