{- | Monadic interface to @libzip@. Most of the operations on zip archive happen within 'Archive' monad (see 'withArchive'). Partial reading of the files in the archive may be performed from within 'Entry' monad (see 'fromFile'). Both 'Archive' and 'Entry' are monad transformers over 'IO', and allow for IO with single and double 'lift'ing respectingly. Note: LibZip does not handle text encodings. Even if its API accepts 'String's (e.g. in 'sourceBuffer'), character codes above 255 should not be used. The user is responsible of proper encoding the text data. /Examples/ List files in the zip archive: @ import System.Environment (getArgs) import Codec.Archive.LibZip main = do (zipfile:_) <- getArgs files <- withArchive [] zipfile $ fileNames [] mapM_ putStrLn files @ Create a zip archive and a add file to the archive: @ import System.Environment (getArgs) import Codec.Archive.LibZip main = do (zipfile:_) <- getArgs withArchive [CreateFlag] zipfile $ do zs <- sourceBuffer \"Hello World!\" addFile \"hello.txt\" zs @ Extract and print a file from the zip archive: @ import System.Environment (getArgs) import Codec.Archive.LibZip main = do (zipfile:file:_) <- getArgs bytes <- withArchive [] zipfile $ fileContents [] file putStrLn bytes @ See also an implementation of a simple zip archiver @hzip.hs@ in the @examples/@ directory of the source distribution. -} module Codec.Archive.LibZip ( -- * Types Archive , Entry , ZipStat(..) -- * Archive operations , withArchive, withEncryptedArchive, getZip , numFiles, fileName, nameLocate, fileNames , fileSize, fileSizeIx , fileStat, fileStatIx , deleteFile, deleteFileIx , renameFile, renameFileIx , addFile, addFileWithFlags , addDirectory, addDirectoryWithFlags , replaceFile, replaceFileIx , setFileCompression, setFileCompressionIx , sourceBuffer, sourceFile, sourceZip , PureSource(..), sourcePure , getComment, setComment, removeComment , getFileComment, getFileCommentIx , setFileComment, setFileCommentIx , removeFileComment, removeFileCommentIx , unchangeFile, unchangeFileIx , unchangeArchive, unchangeAll -- * File reading operations , fromFile, fromFileIx , readBytes, skipBytes, readContents , fileContents, fileContentsIx -- * Flags and options , OpenFlag(..) , FileFlag(..) , ZipCompMethod(..) , ZipEncryptionMethod(..) -- * Exception handling , ZipError(..) , catchZipError -- * Re-exports , lift ) where import Bindings.LibZip import Codec.Archive.LibZip.Types import Codec.Archive.LibZip.Errors import Data.Time.Clock (UTCTime, getCurrentTime) import Data.Time.Clock.POSIX (utcTimeToPOSIXSeconds) import Data.Word (Word8) import Control.Monad (when) import Control.Monad.State.Strict (StateT(..), MonadState(..), MonadTrans(..), lift, liftM) import Foreign.C.Error (Errno(..), eINVAL) import Foreign.C.String (withCString, peekCString) import Foreign.C.Types (CInt, CULLong) import Foreign.Marshal.Alloc (alloca) import Foreign.Marshal.Array (allocaArray, peekArray, withArrayLen, pokeArray) import Foreign.Marshal.Utils (with) import Foreign.Ptr (Ptr, nullPtr, castPtr) import Foreign.Storable (Storable, peek, poke, pokeElemOff, sizeOf) import qualified Control.Exception as E import qualified Data.ByteString as BS import qualified Data.ByteString.UTF8 as UTF8 -- -- Types -- -- | Monadic computation with a zip archive. See 'withArchive'. type Archive a = StateT Zip IO a -- | Monadic computation to read from open archive entries. -- See 'fromFile' and 'fromFileIx'. type Entry a = StateT (ZipFile,Integer,[FileFlag]) -- (file, position index, access flags) (StateT Zip IO) -- archive monad a -- -- Archive operations -- -- | Top-level wrapper for operations with an open -- archive. 'withArchive' opens and closes the file -- automatically. On error it throws 'ZipError'. withArchive :: [OpenFlag] -- ^ Checks for consistency or existence. -> FilePath -- ^ Filename of the zip archive. -> Archive a -- ^ Action to do with the archive. -> IO a withArchive flags path action = withCString path $ \path' -> alloca $ \errp -> c'zip_open path' (combine flags) errp >>= \z -> if z == nullPtr then peek errp >>= E.throwIO. errFromCInt else withOpenArchive z action -- | Top-level wrapper for operations with an open encrypted archive. -- 'withEncryptedArchive' opens and closes the file automatically. -- On error it throws 'ZipError'. withEncryptedArchive :: [OpenFlag] -- ^ Checks for consistency or existence. -> String -- ^ Encryption password. -> FilePath -- ^ Filename of the zip archive. -> Archive a -- ^ Action to don with the archive. -> IO a withEncryptedArchive flags password path action = withCString password $ \password' -> withCString path $ \path' -> alloca $ \errp -> c'zip_open path' (combine flags) errp >>= \z -> if z == nullPtr then peek errp >>= E.throwIO. errFromCInt else do r <- c'zip_set_default_password z password' if r /= 0 then get_error z >>= E.throwIO else withOpenArchive z action withOpenArchive :: Zip -> Archive a -> IO a withOpenArchive z action = do r <- fst `liftM` runStateT action z e <- c'zip_close z if e /= 0 then get_error z >>= E.throwIO else return r -- | Get the number of entries in the archive. numFiles :: [FileFlag] -- ^ 'FileUNCHANGED' can be used to return -- the original unchanged number of entries. -> Archive Integer numFiles flags = do z <- getZip lift $ fromIntegral `liftM` c'zip_get_num_entries z (combine flags) -- | Get name of an entry in the archive by its index. fileName :: [FileFlag] -- ^ 'FileUNCHANGED' flag can be used to -- return the original unchanged filename. -> Integer -- ^ Position index of a file in the archive. -> Archive FilePath -- ^ Name of the file in the archive. fileName flags i = do z <- getZip lift $ do n <- c'zip_get_name z (fromIntegral i) (combine flags) doIf' (n /= nullPtr) z $ peekCString n -- | Locate an entry (get its index) in the archive by its name. nameLocate :: [FileFlag] -- ^ Filename lookup mode. -- 'FileNOCASE': ignore case distinctions (only for ASCII). -- 'FileNODIR': ignore directory part of the file name. -- 'FileENC_RAW': compare against unmodified names as it is -- in the ZIP archive. -- 'FileENC_GUESS': (default) guess encoding of the name in -- the ZIP archive and convert it to UTF-8, -- if necessary. -- 'FileENC_STRICT': follow the ZIP specification and expect -- CP-437 encoded names in the ZIP archive -- (except if they are explicitly marked as -- UTF-8). Convert it to UTF-8 before comparing. -> FilePath -- ^ Name of the file in the archive. -> Archive (Maybe Integer) -- ^ 'Just' position index if found. nameLocate flags name = do z <- getZip lift $ withCString name $ \name' -> do i <- fromIntegral `liftM` c'zip_name_locate z name' (combine flags) if i < 0 then return Nothing else return (Just i) -- | Get names of all entries (files and directories) in the archive. fileNames :: [FileFlag] -- ^ 'FileUNCHANGED' flag is accepted. -> Archive [FilePath] fileNames flags = do n <- numFiles flags mapM (fileName flags) [0..n-1] -- | Get size of a file in the archive. fileSize :: [FileFlag] -- ^ Filename lookup mode, 'FileUNCHANGED' can be used. -> FilePath -- ^ Name of the file in the archive. -> Archive Integer -- ^ File size. fileSize flags name = fileStat flags name >>= return . zs'size -- | Get size of a file in the archive (by index). fileSizeIx :: [FileFlag] -- ^ 'FileUNCHANGED' is accepted. -> Integer -- ^ Position index of a file in the archive. -> Archive Integer -- ^ File size. fileSizeIx flags i = fileStatIx flags i >>= return . zs'size -- | Get information about a file in the archive. fileStat :: [FileFlag] -- ^ Filename lookup mode, 'FileUNCHANGED' can be used. -> FilePath -- ^ Name of the file in the archive. -> Archive ZipStat -- ^ Infomation about the file. fileStat flags name = do z <- getZip lift $ withCString name $ \name' -> alloca $ \stat -> do c'zip_stat_init stat r <- c'zip_stat z name' (combine flags) stat doIf' (r == 0) z $ toZipStat =<< peek stat -- | Get information about a file in the archive (by index). fileStatIx :: [FileFlag] -- ^ 'FileUNCHANGED' can be used. -> Integer -- ^ Position index of a file in the archive. -> Archive ZipStat -- ^ Information about the file. fileStatIx flags i = do z <- getZip lift $ alloca $ \stat -> do r <- c'zip_stat_index z (fromIntegral i) (combine flags) stat doIf' (r == 0) z $ toZipStat =<< peek stat -- | Delete file from the archive. deleteFile :: [FileFlag] -- ^ Filename lookup mode (see 'nameLocate'). -> FilePath -- ^ Filename. -> Archive () deleteFile flags name = do mbi <- nameLocate flags name maybe (lift $ E.throwIO ErrNOENT) deleteFileIx mbi -- | Delete file (referenced by position index) from the archive. deleteFileIx :: Integer -- ^ Position index of a file in the archive. -> Archive () deleteFileIx i = do z <- getZip r <- lift $ c'zip_delete z (fromIntegral i) if r == 0 then return () else lift $ get_error z >>= E.throwIO -- | Rename file in the archive. renameFile :: [FileFlag] -- ^ Filename lookup mode (see 'nameLocate'). -> FilePath -- ^ Old name. -> FilePath -- ^ New name. -> Archive () renameFile flags oldname newname = do mbi <- nameLocate flags oldname maybe (lift $ E.throwIO ErrNOENT) (\i -> renameFileIx i (UTF8.fromString newname) [FileENC_UTF_8]) mbi -- | Rename file (referenced by position index) in the archive. renameFileIx :: Integer -- ^ Position index of a file in the archive. -> BS.ByteString -- ^ New name. -> [FileFlag] -- ^ Name encoding flags. -- 'FileENC_GUESS': guess encoding of the name (default). -- 'FileENC_UTF_8': interpret name as UTF-8. -- 'FileENC_CP437': interpret name as CP-437. -> Archive () renameFileIx i newname flags = do z <- getZip r <- lift $ BS.useAsCString newname $ \s -> c'zip_file_rename z (fromIntegral i) s (combine flags) if r == 0 then return () else lift $ get_error z >>= E.throwIO -- | Add a file to the archive. addFile :: FilePath -- ^ Name of the file to create. -> ZipSource -- ^ Source where file data is obtained from. -> Archive Int -- ^ Position index of the new file. addFile name src = let utf8name = UTF8.fromString name in addFileWithFlags [FileENC_UTF_8] utf8name src addFileWithFlags :: [FileFlag] -- ^ Can be a combination of 'FileOVERWRITE' and/or one of -- filename encoding flags: 'FileENC_GUESS' (default), -- 'FileENC_UTF_8', 'FileENC_CP437'. -> BS.ByteString -- ^ Name of the file to create. -> ZipSource -- ^ Source where file data is obtained from. -> Archive Int -- ^ Position index of the new file. addFileWithFlags flags namebytes src = do z <- getZip lift $ BS.useAsCString namebytes $ \name' -> do i <- c'zip_file_add z name' src (combine flags) if i < 0 then c'zip_source_free src >> get_error z >>= E.throwIO else return $ fromIntegral i -- | Add a directory to the archive. addDirectory :: FilePath -- ^ Directory's name in the archive. -> Archive Int -- ^ Position index of the new directory entry. addDirectory name = let utf8name = UTF8.fromString name in addDirectoryWithFlags [FileENC_UTF_8] utf8name -- | Add a directory to the archive. addDirectoryWithFlags :: [FileFlag] -- ^ Can be one of filename encoding flags: -- 'FileENC_GUESS (default), 'FileENC_UTF_8', 'FileENC_CP437'. -> BS.ByteString -- ^ Directory's name in the archive. -> Archive Int -- ^ Position index of the new directory entry. addDirectoryWithFlags flags name = do z <- getZip r <- lift $ BS.useAsCString name $ \name'-> c'zip_dir_add z name' (combine flags) if r < 0 then lift $ get_error z >>= E.throwIO else return (fromIntegral r) -- | Replace a file in the archive. replaceFile :: [FileFlag] -- ^ Filename lookup mode (see 'nameLocate'). -> FilePath -- ^ File to replace. -> ZipSource -- ^ Source where the new file data is obtained from. -> Archive () replaceFile flags name src = do mbi <- nameLocate flags name maybe (lift $ c'zip_source_free src >> E.throwIO ErrNOENT) (\i -> replaceFileIx i src >> return ()) mbi -- | Set compression method for a file in the archive. setFileCompression :: [FileFlag] -- ^ Filename lookup mode (see 'nameLocate'). -> FilePath -- ^ Filename. -> ZipCompMethod -- ^ Compression method. -- As of libzip 0.11, the following methods are supported: -- 'CompDEFAULT', 'CompSTORE', 'CompDEFLATE'. -> Archive () setFileCompression flags name method = do mbi <- nameLocate flags name maybe (lift $ E.throwIO ErrNOENT) (\i -> setFileCompressionIx i method) mbi -- | Set compression method for a file in the archive. setFileCompressionIx :: Integer -- ^ Position index of a file in the archive. -> ZipCompMethod -- ^ Compression method. -- As of libzip 0.11, the following methods are supported: -- 'CompDEFAULT', 'CompSTORE', 'CompDEFLATE'. -> Archive () setFileCompressionIx i method = do z <- getZip lift $ do r <- c'zip_set_file_compression z (fromIntegral i) (fromIntegral . fromEnum $ method) 0 if r /= 0 then get_error z >>= E.throwIO else return () -- | Replace a file in the archive (referenced by position index). replaceFileIx :: Integer -- ^ Position index of a file in the archive. -> ZipSource -- ^ Source where the new file data is obtained from -> Archive () replaceFileIx i src = do z <- getZip lift $ do r <- c'zip_file_replace z (fromIntegral i) src 0 if r < 0 then c'zip_source_free src >> get_error z >>= E.throwIO else return () -- | Create a data source. Note: input is converted to @[Word8]@ internally. sourceBuffer :: (Enum a) => [a] -> Archive ZipSource sourceBuffer src = do let ws = map (toEnum . fromEnum) src :: [Word8] z <- getZip lift $ withArrayLen ws $ \len buf -> do zs <- c'zip_source_buffer z (castPtr buf) (fromIntegral len) 0 if zs == nullPtr then get_error z >>= E.throwIO else return zs -- | Create a data source from a file. sourceFile :: FilePath -- ^ File to open. -> Integer -- ^ Offset from the beginning of the file. -> Integer -- ^ The number of bytes to read. If @0@ or @-1@, -- the read till the end of file. -> Archive ZipSource sourceFile name offset len = do z <- getZip lift $ withCString name $ \name' -> do zs <- c'zip_source_file z name' (fromIntegral offset) (fromIntegral len) if zs == nullPtr then get_error z >>= E.throwIO else return zs -- | Create a data source from a file in the zip archive. sourceZip :: [FileFlag] -- ^ 'FileUNCHANGED' and 'FileRECOMPRESS' can be used. -> Zip -- ^ Source archive. -> Integer -- ^ Position index of a file in the source archive. -> Integer -- ^ Offset from the beginning of the file. -> Integer -- ^ The number of bytes to read. If @0@ or @-1@, -- then read till the end of file. -> Archive ZipSource sourceZip flags srcz srcidx offset len = do z <- getZip lift $ do zs <- c'zip_source_zip z srcz (fromIntegral srcidx) (combine flags) (fromIntegral offset) (fromIntegral len) if zs == nullPtr then get_error z >>= E.throwIO else return zs -- | Create a data source from a 'PureSource'. -- Note: input of @[a]@ is converted to @[Word8]@ internally. sourcePure :: (Enum a, Storable a, Storable st, Integral szt) => PureSource a st szt -> Archive ZipSource sourcePure pureSrc = do z <- getZip lift $ do cb <- mk'zip_source_callback (runPureSource pureSrc) zs <- with (srcState pureSrc) $ \pState -> c'zip_source_function z cb (castPtr pState) if zs == nullPtr then get_error z >>= E.throwIO else return zs -- | Wrapper for a user-provided pure function to be used with 'sourcePure'. -- Data size should be known in advance ('srcSize'). -- The function should support reading by chunks ('readSrc'). data PureSource a st szt = PureSource { srcState :: st -- ^ Initial state of the source. , srcSize :: szt -- ^ Total size of the data. , srcMTime :: Maybe UTCTime -- ^ Modification time (current time if Nothing). , readSrc :: szt -> st -> Maybe (szt, [a], st) -- ^ Read a chunk of the data, return @Just@ the size -- of data read, the data themselves and the new state -- of the source, or @Nothing@ on error. } runPureSource :: (Enum a, Storable a, Storable st, Integral szt) => PureSource a st szt -> (Ptr () -> Ptr () -> CULLong -> C'zip_source_cmd -> IO CULLong) runPureSource src pState pData len cmd | cmd == c'ZIP_SOURCE_OPEN = return 0 | cmd == c'ZIP_SOURCE_READ = do s <- peek (castPtr pState :: Ptr st) case readSrc (src { srcState = s }) (fromIntegral len) s of Just (len',bs,s') -> do pokeArray (castPtr pData :: Ptr Word8) (map (toEnum.fromEnum) bs) poke (castPtr pState) s' return (fromIntegral len') Nothing -> return (-1) | cmd == c'ZIP_SOURCE_CLOSE = return 0 | cmd == c'ZIP_SOURCE_STAT = do t <- maybe getCurrentTime return (srcMTime src) let pt = fromInteger . round . utcTimeToPOSIXSeconds $ t let pStat = castPtr pData c'zip_stat_init pStat stat <- peek pStat let stat' = stat { c'zip_stat'mtime = pt , c'zip_stat'size = fromIntegral $ srcSize src } poke pStat stat' return $ fromIntegral (sizeOf stat') | cmd == c'ZIP_SOURCE_ERROR = do let pErrs = castPtr pData :: Ptr CInt poke pErrs (fromIntegral . fromEnum $ ErrINVAL) let (Errno esys) = eINVAL pokeElemOff pErrs 1 esys return $ fromIntegral (2 * sizeOf esys) | cmd == c'ZIP_SOURCE_FREE = return 0 | otherwise = return (-1) -- | Get zip archive comment. getComment :: [FileFlag] -- ^ Can be a combination of 'FileUNCHANGED' and/or -- one of 'FileENC_GUESS' (default), 'FileENC_STRICT' (CP-437). -> Archive (Maybe String) getComment flags = do z <- getZip (c,n) <- lift $ alloca $ \lenp -> do c <- c'zip_get_archive_comment z lenp (combine flags) n <- peek lenp return (c,n) if c == nullPtr then return Nothing else lift $ BS.packCStringLen (c, fromIntegral n) >>= return . Just . UTF8.toString -- | Set zip archive comment. setComment :: String -- ^ Comment message. -> Archive () setComment msg = do z <- getZip let utf8msg = UTF8.fromString msg r <- lift $ BS.useAsCStringLen utf8msg $ \(msg',i') -> c'zip_set_archive_comment z msg' (fromIntegral i') if r < 0 then lift $ get_error z >>= E.throwIO else return () -- | Remove zip archive comment. removeComment :: Archive () removeComment = do z <- getZip r <- lift $ c'zip_set_archive_comment z nullPtr 0 if r < 0 then lift $ get_error z >>= E.throwIO else return () -- | Get comment for a file in the archive. getFileComment :: [FileFlag] -- ^ Filename lookup mode (see 'nameLocate'). -> FilePath -- ^ Filename -> Archive (Maybe String) getFileComment flags name = do mbi <- nameLocate flags name -- Backwards compatibility with LibZip < 0.11: FileUNCHANGED flag from -- the filename lookup mode was used to get the original unchanged comment. -- Please don't rely on this feature and use 'getFileCommentIx' instead. let comment_flags = filter (== FileUNCHANGED) flags maybe (lift $ E.throwIO ErrNOENT) (\i -> do mbs <- getFileCommentIx comment_flags i -- 'FileENC_GUESS' is default => mbs is UTF-8 encoded return $ liftM UTF8.toString mbs ) mbi -- | Get comment for a file in the archive (referenced by position index). getFileCommentIx :: [FileFlag] -- ^ Comment lookup flags. -- 'FileUNCHANGED': return the original unchanged comment. -- 'FileENC_RAW': return the unmodified commment as it is. -- 'FileENC_GUESS': (default) guess the encoding of the comment -- and convert it to UTF-8, if necessary. -- 'FileENC_STRICT': follow the ZIP specification for file names -- and extend it to file comments, expect -- them to be encoded in CP-437. Convert it -- to UTF-8. -> Integer -- ^ Position index of the file. -> Archive (Maybe BS.ByteString) getFileCommentIx flags i = do z <- getZip (c,n) <- lift $ alloca $ \lenp -> do c <- c'zip_file_get_comment z (fromIntegral i) lenp (combine flags) n <- peek lenp return (c,n) if c == nullPtr then return Nothing else lift $ BS.packCStringLen (c,fromIntegral n) >>= return . Just -- | Set comment for a file in the archive. setFileComment :: [FileFlag] -- ^ Filename lookup mode (see 'nameLocate'). -> FilePath -- ^ Filename. -> String -- ^ New file comment. -> Archive () setFileComment flags path comment = do mbi <- nameLocate flags path let utf8comment = UTF8.fromString comment let cflags = [FileENC_UTF_8] maybe (lift $ E.throwIO ErrNOENT) (\i -> setFileCommentIx i utf8comment cflags) mbi -- | Set comment for a file in the archive (referenced by position index). setFileCommentIx :: Integer -- ^ Position index of a file in the archive. -> BS.ByteString -- ^ New file comment. -> [FileFlag] -- ^ Comment encoding flags. -- 'FileENC_GUESS': guess encoding of the comment (default). -- 'FileENC_UTF_8': interpret comment as UTF-8. -- 'FileENC_CP437': interpret comment as CP-437. -> Archive () setFileCommentIx i comment cflags = do z <- getZip r <- lift $ BS.useAsCStringLen comment $ \(msg,len) -> c'zip_file_set_comment z (fromIntegral i) msg (fromIntegral len) (combine cflags) if r < 0 then lift $ get_error z >>= E.throwIO else return () -- | Remove comment for a file in the archive. removeFileComment :: [FileFlag] -- ^ Filename lookup mode (see 'nameLocate'). -> FilePath -- ^ Filename. -> Archive () removeFileComment flags path = do mbi <- nameLocate flags path maybe (lift $ E.throwIO ErrNOENT) removeFileCommentIx mbi -- | Remove comment for a file in the archive (referenced by position index). removeFileCommentIx :: Integer -- ^ Position index of a file in the archive. -> Archive () removeFileCommentIx i = do let flags = 0 -- file name encoding flags (*_FL_*) are irrelevant z <- getZip r <- lift $ c'zip_file_set_comment z (fromIntegral i) nullPtr 0 flags if r < 0 then lift $ get_error z >>= E.throwIO else return () -- | Undo changes to a file in the archive. unchangeFile :: [FileFlag] -- ^ Filename lookup mode (see 'nameLocate'). -> FilePath -- ^ Filename. -> Archive () unchangeFile flags name = do mbi <- nameLocate flags name maybe (lift $ E.throw ErrNOENT) unchangeFileIx mbi -- | Undo changes to a file in the archive (referenced by position index). unchangeFileIx :: Integer -- ^ Position index of a file in the archive. -> Archive () unchangeFileIx i = do z <- getZip lift $ do r <- c'zip_unchange z (fromIntegral i) if r < 0 then get_error z >>= E.throwIO else return () -- | Undo global changes to zip archive (revert changes to the archive -- comment and global flags). unchangeArchive :: Archive () unchangeArchive = do z <- getZip lift $ do r <- c'zip_unchange_archive z if r < 0 then get_error z >>= E.throwIO else return () -- | Undo all changes in a zip archive. unchangeAll :: Archive () unchangeAll = do z <- getZip lift $ do r <- c'zip_unchange_all z if r < 0 then get_error z >>= E.throwIO else return () -- -- File reading operations -- -- | Wrapper for operations with a file in the archive. 'fromFile' is normally -- called from within an 'Archive' action (see also 'withArchive'). -- 'fromFile' can be replaced with 'fileContents' to read an entire file at -- once. fromFile :: [FileFlag] -- ^ Filename lookup mode, -- 'FileCOMPRESSED' and 'FileUNCHANGED' can be used. -> FilePath -- ^ Name of the file in the arhive. -> Entry a -- ^ Action with the file. -> Archive a fromFile flags name action = do z <- getZip nameLocate flags name >>= maybe (lift $ get_error z >>= E.throwIO) runAction where runAction i = do z <- getZip zf <- lift $ withCString name $ \n -> c'zip_fopen z n (combine flags) if zf == nullPtr then lift $ get_error z >>= E.throwIO else do r <- fst `liftM` runStateT action (zf,i,flags) e <- lift $ c'zip_fclose zf if e /= 0 then lift $ E.throwIO $ (toEnum . fromIntegral $ e :: ZipError) else return r -- | Wrapper for operations with a file in the archive. File is referenced -- by index (position). 'fromFileIx' is normally called from within -- an 'Archive' action (see also 'withArchive'). 'fromFileIx' can be replaced -- with 'fileContentsIx' to read an entire file at once. fromFileIx :: [FileFlag] -- ^ 'FileCOMPRESSED' and 'FileUNCHANGED' can be used. -> Integer -- ^ Position index of a file in the archive. -> Entry a -- ^ Action with the file. -> Archive a fromFileIx flags i action = do z <- getZip zf <- lift $ c'zip_fopen_index z (fromIntegral i) (combine flags) if zf == nullPtr then lift $ get_error z >>= E.throwIO else do r <- fst `liftM` runStateT action (zf,i,flags) e <- lift $ c'zip_fclose zf if e /= 0 then lift $ E.throwIO $ (toEnum . fromIntegral $ e :: ZipError) else return r -- | Read at most @n@ bytes from the file. readBytes :: (Enum a) => Integer -- ^ The number of bytes to read. -> Entry [a] -- ^ Bytes read. readBytes n = do lift . lift $ when (n > toInteger (maxBound::Int)) (E.throwIO ErrMEMORY) -- allocaArray can't allocate > (maxBound::Int) (zf,_,_) <- get lift . lift $ allocaArray (fromIntegral n) $ \buf -> do nread <- c'zip_fread zf (castPtr buf) (fromIntegral n) if nread < 0 then get_file_error zf >>= E.throwIO else do bs <- peekArray (fromIntegral nread) buf :: IO [Word8] return . map (toEnum . fromEnum) $ bs -- | Skip @n@ bytes from the open file. Note: this is not faster than reading. skipBytes :: Integer -> Entry () skipBytes n = (readBytes n :: Entry [Word8]) >> return () -- | Read entire file contents. readContents :: (Enum a) => Entry [a] -- ^ Contents of the file. readContents = do (_,i,flags) <- get sz <- lift $ fileSizeIx flags i readBytes sz -- | Read entire file. Shortcut for 'readContents' from within 'Archive' monad. fileContents :: (Enum a) => [FileFlag] -> FilePath -> Archive [a] fileContents flags name = fromFile flags name readContents -- | Read entire file (referenced by position index). Shortcut for -- 'readContents' from within 'Archive' monad. fileContentsIx :: (Enum a) => [FileFlag] -> Integer -> Archive [a] fileContentsIx flags i = fromFileIx flags i readContents -- -- Helpers -- -- | Get archive handler. Throw 'ErrINVAL' if the archive is closed. getZip :: Archive Zip getZip = do z <- get if z == nullPtr then lift $ E.throwIO ErrINVAL else return z -- | Get and throw a 'ZipError' if condition fails. Otherwise work normally. doIf :: Bool -> Zip -> (Zip -> IO a) -> IO a doIf cnd z action = if cnd then action z else get_error z >>= E.throwIO -- | Get and throw a 'ZipError' if condition fails. See also 'doIf'. doIf' :: Bool -> Zip -> (IO a) -> IO a doIf' cnd z action = doIf cnd z (const action)