| Safe Haskell | None |
|---|
Codec.Archive.Zip
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
- type Archive = StateT Zip IO
- withArchive :: FilePath -> Archive a -> IO a
- getComment :: Archive ByteString
- setComment :: ByteString -> Archive ()
- entryNames :: Archive [FilePath]
- sourceEntry :: FilePath -> Sink ByteString (ResourceT Archive) a -> Archive a
- sinkEntry :: FilePath -> Source (ResourceT Archive) ByteString -> Archive ()
- sinkEntryUncompressed :: FilePath -> Source (ResourceT Archive) ByteString -> Archive ()
- extractFiles :: [FilePath] -> FilePath -> Archive ()
- addFiles :: [FilePath] -> Archive ()
- fileNames :: Archive [FilePath]
- getSource :: MonadResource m => FilePath -> Archive (Source m ByteString)
- getSink :: MonadResource m => FilePath -> UTCTime -> Archive (Sink ByteString m ())
Archive monad
withArchive :: FilePath -> Archive a -> IO aSource
Operations
setComment :: ByteString -> Archive ()Source
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
extractFiles :: [FilePath] -> FilePath -> Archive ()Source
Deprecated
getSource :: MonadResource m => FilePath -> Archive (Source m ByteString)Source
getSink :: MonadResource m => FilePath -> UTCTime -> Archive (Sink ByteString m ())Source