| Safe Haskell | Safe-Infered |
|---|
Codec.Archive.Zip
Description
Sink file to the archive:
import Data.Time (getCurrentTime)
import System.Environment (getArgs)
import System.FilePath (takeFileName)
import Data.Conduit
import qualified Data.Conduit.Binary as CB
import Codec.Archive.Zip
main = do
filePath:_ <- getArgs
time <- getCurrentTime
withArchive "some.zip" $ do
sink <- getSink (takeFileName filePath) time
runResourceT $ CB.sourceFile filePath $$ sink
Source first file from the archive:
import System.Environment (getArgs)
import Data.Conduit
import qualified Data.Conduit.Binary as CB
import Codec.Archive.Zip
main = do
archivePath:_ <- getArgs
withArchive archivePath $ do
fileName:_ <- fileNames
source <- getSource fileName
runResourceT $ source $$ CB.sinkFile fileName
List files in the zip archive:
import System.Environment (getArgs)
import Codec.Archive.Zip
main = do
archivePath:_ <- getArgs
names <- withArchive archivePath fileNames
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 all files from the archive:
import System.Environment (getArgs)
import Codec.Archive.Zip
main = do
dirPath:_ <- getArgs
withArchive "some.zip" $ do
names <- fileNames
extractFiles names dirPath
- type Archive a = StateT Zip IO a
- withArchive :: FilePath -> Archive a -> IO a
- getComment :: Archive ByteString
- setComment :: ByteString -> Archive ()
- fileNames :: Archive [FilePath]
- getSource :: MonadResource m => FilePath -> Archive (Source m ByteString)
- getSink :: MonadResource m => FilePath -> UTCTime -> Archive (Sink ByteString m ())
- addFiles :: [FilePath] -> Archive ()
- extractFiles :: [FilePath] -> FilePath -> Archive ()
Archive monad
withArchive :: FilePath -> Archive a -> IO aSource
Operations
setComment :: ByteString -> Archive ()Source
Conduit interface
getSource :: MonadResource m => FilePath -> Archive (Source m ByteString)Source
getSink :: MonadResource m => FilePath -> UTCTime -> Archive (Sink ByteString m ())Source