zip-stream-0.2.1.0: ZIP archive streaming using conduits
Safe HaskellNone
LanguageHaskell2010

Codec.Archive.Zip.Conduit.Zip

Description

Stream the creation of a zip file, e.g., as it's being uploaded.

Synopsis

Documentation

zipStream :: (MonadThrow m, PrimMonad m) => ZipOptions -> ConduitM (ZipEntry, ZipData m) ByteString m Word64 Source #

Stream produce a zip file, reading a sequence of entries with data. Although file data is never kept in memory (beyond a single ZipDataByteString), the format of zip files requires producing a final directory of entries at the end of the file, consuming an additional ~100 bytes of state per entry during streaming. The final result is the total size of the zip file.

Depending on options, the resulting zip file should be compatible with most unzipping applications. Any errors are thrown in the underlying monad (as ZipErrors).

data ZipOptions Source #

Options controlling zip file parameters and features

Constructors

ZipOptions 

Fields

  • zipOpt64 :: Bool

    Allow ZipDataSources over 4GB (reduces compatibility in some cases); this is automatically enabled for any files of known size (e.g., zipEntrySize)

  • zipOptCompressLevel :: Int

    Compress zipped files (0 = store only, 1 = minimal, 9 = best; non-zero improves compatibility, since some unzip programs don't supported stored, streamed files, including the one in this package)

  • zipOptInfo :: ZipInfo

    Other parameters to store in the zip file

data ZipInfo Source #

Summary information at the end of a zip stream.

Constructors

ZipInfo 

Instances

Instances details
Eq ZipInfo Source # 
Instance details

Defined in Codec.Archive.Zip.Conduit.Types

Methods

(==) :: ZipInfo -> ZipInfo -> Bool #

(/=) :: ZipInfo -> ZipInfo -> Bool #

Show ZipInfo Source # 
Instance details

Defined in Codec.Archive.Zip.Conduit.Types

data ZipEntry Source #

(The beginning of) a single entry in a zip stream, which may be any file or directory. As per zip file conventions, directory names should end with a slash and have no data, but this library does not ensure that.

Constructors

ZipEntry 

Fields

Instances

Instances details
Eq ZipEntry Source # 
Instance details

Defined in Codec.Archive.Zip.Conduit.Types

Show ZipEntry Source # 
Instance details

Defined in Codec.Archive.Zip.Conduit.Types

data ZipData m Source #

The data contents for a ZipEntry. For empty entries (e.g., directories), use mempty.

Constructors

ZipDataByteString ByteString

A known ByteString, which will be fully evaluated (not streamed)

ZipDataSource (ConduitM () ByteString m ())

A byte stream producer, streamed (and compressed) directly into the zip

Instances

Instances details
Monad m => Semigroup (ZipData m) Source # 
Instance details

Defined in Codec.Archive.Zip.Conduit.Types

Methods

(<>) :: ZipData m -> ZipData m -> ZipData m #

sconcat :: NonEmpty (ZipData m) -> ZipData m #

stimes :: Integral b => b -> ZipData m -> ZipData m #

Monad m => Monoid (ZipData m) Source # 
Instance details

Defined in Codec.Archive.Zip.Conduit.Types

Methods

mempty :: ZipData m #

mappend :: ZipData m -> ZipData m -> ZipData m #

mconcat :: [ZipData m] -> ZipData m #