zip-conduit-0.2: Working with zip archives via conduits.

Safe HaskellSafe-Infered

Codec.Archive.Zip

Contents

Description

Sink entries to the archive:

{-# LANGUAGE OverloadedStrings #-}

import qualified Data.Conduit.Binary as CB
import           Codec.Archive.Zip

main = do
    withArchive "some.zip" $ do
        sinkEntry "first"  $ CB.sourceLbs "hello"
        sinkEntry "second" $ CB.sourceLbs "world"

Source first entry from the archive:

import           System.Environment (getArgs)
import qualified Data.Conduit.Binary as CB
import           Codec.Archive.Zip

main = do
    archivePath:_ <- getArgs
    withArchive archivePath $ do
        name:_ <- entryNames
        sourceEntry name $ CB.sinkFile name

List entries in the archive:

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

main = do
    archivePath:_ <- getArgs
    names <- withArchive archivePath entryNames
    mapM_ putStrLn names

Add files to the archive:

import Control.Monad (filterM)
import System.Directory (doesFileExist, getDirectoryContents)
import System.Environment (getArgs)
import Codec.Archive.Zip

main = do
    dirPath:_ <- getArgs
    paths     <- getDirectoryContents dirPath
    filePaths <- filterM doesFileExist paths
    withArchive "some.zip" $ addFiles filePaths

Extract files from the archive:

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

main = do
    dirPath:_ <- getArgs
    withArchive "some.zip" $ do
        names <- entryNames
        extractFiles names dirPath

Synopsis

Archive monad

Operations

Conduit interface

sourceEntry :: FilePath -> Sink ByteString (ResourceT Archive) a -> Archive aSource

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

sinkEntry :: FilePath -> Source (ResourceT Archive) ByteString -> Archive ()Source

Stream data from the specified source to an archive entry.

sinkEntryUncompressed :: FilePath -> Source (ResourceT Archive) ByteString -> Archive ()Source

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

High level functions

Deprecated