zip-conduit-0.3.0: Working with zip archives via conduits
Safe HaskellSafe-Inferred
LanguageHaskell2010

Codec.Archive.Zip

Description

Sink entries to the archive:

{-# LANGUAGE OverloadedStrings #-}

import Data.Conduit.Combinators
import Codec.Archive.Zip

main :: IO ()
main = do
    withArchive "some.zip" $ do
        sinkEntry "first"  $ sourceLazy "hello"
        sinkEntry "second" $ sourceLazy "world"

Source first entry from the archive:

import System.Environment (getArgs)
import Data.Conduit.Combinators
import Codec.Archive.Zip

main :: IO ()
main = do
    archivePath:_ <- getArgs
    withArchive archivePath $ do
        name:_ <- entryNames
        sourceEntry name $ sinkFile name

List entries in the archive:

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

main :: IO ()
main = do
    archivePath:_ <- getArgs
    names <- withArchive archivePath entryNames
    mapM_ putStrLn names
Synopsis

Archive monad

type Archive = StateT Zip IO Source #

Operations

Conduit interface

sourceEntry :: FilePath -> ConduitT ByteString Void (ResourceT IO) a -> Archive a Source #

Stream the contents of an archive entry to the specified sink.

sinkEntry :: FilePath -> ConduitT () ByteString (ResourceT IO) () -> Archive () Source #

Stream data from the specified source to an archive entry.

sinkEntryUncompressed :: FilePath -> ConduitT () ByteString (ResourceT IO) () -> Archive () Source #

Stream data from the specified source to an uncompressed archive entry.

High level functions

extractFiles :: [FilePath] -> FilePath -> Archive () Source #

Extracts files from the Zip to a directory.

addFiles :: [FilePath] -> Archive () Source #

Appends files to the Zip. The file paths are used verbatim as zip entry names, save for the application of dropDrive.

addFilesAs :: (FilePath -> FilePath) -> [FilePath] -> Archive () Source #

Appends files to the Zip using a function to transform the file paths into zip entry names. Useful when dealing with absolute paths. dropDrive is applied to the paths before the supplied function.

Deprecated