-- | This module is a backwards compatible replacement for @Codec.Archive.LibZip@ module of LibZip 0.0.x. This API is deprecated, please don't use it in new code. module Codec.Archive.LibZip.LegacyZeroZero {-# DEPRECATED "Please upgrade to monadic Codec.Archive.LibZip" #-} ( -- * Types Zip,ZipFile,OpenFlag(..),FileFlag(..),ZipError(..) ,Word8 -- * High-level interface ,withZip,getFiles,getFileSize ,readZipFile,readZipFile' ,readZipFileHead,readZipFileHead' -- * Low-level bindings ,open,close,get_num_files,get_name ,fopen,fopen_index,fclose,fread -- * Utilities ,catchZipError,isFile,isDir ) where import Control.Monad (liftM) import Data.Word (Word8) import Foreign.C.String (withCString,peekCString) import Foreign.Marshal.Alloc (alloca) import Foreign.Marshal.Array (allocaArray, peekArray) import Foreign.Ptr (Ptr, nullPtr, castPtr) import Foreign.Storable (peek) import qualified Control.Exception as E import qualified Data.ByteString as B import Bindings.LibZip import Codec.Archive.LibZip.Types import Codec.Archive.LibZip.Errors -- | Open zip archive specified by /path/ and return its handler on success. open :: String -- ^ /path/ of the file to open -> [OpenFlag] -- ^ open mode -> IO Zip -- ^ handler of the open zip archive open path flags = withCString path $ \path' -> alloca $ \errp -> do z <- c'zip_open path' (combine flags) errp if z /= nullPtr then return z else peek errp >>= E.throwIO . errFromCInt -- | Close zip archive. close :: Zip -> IO () close z | z == nullPtr = E.throwIO ErrINVAL close z = do r <- c'zip_close z if r == 0 then return () else E.throwIO =<< get_error z -- | Return the number of files in the archive. get_num_files :: Zip -> IO Int get_num_files z | z == nullPtr = E.throwIO ErrINVAL get_num_files z = fromIntegral `liftM` c'zip_get_num_files z -- | Get name of file by index. get_name :: Zip -> Int -> [FileFlag] -> IO String get_name z _ _ | z == nullPtr = E.throwIO ErrINVAL get_name z i flags = do n <- c'zip_get_name z (fromIntegral i) (combine flags) if n /= nullPtr then peekCString n else E.throwIO =<< get_error z -- | Open file in zip archive for reading. fopen :: Zip -> String -> [FileFlag] -> IO ZipFile fopen z _ _ | z == nullPtr = E.throwIO ErrINVAL fopen z fn flags = withCString fn $ \fn' -> returnNotNull z =<< c'zip_fopen z fn' (combine flags) -- | Open n-th file in zip archive for reading. fopen_index :: Zip -> Int -> [FileFlag] -> IO ZipFile fopen_index z _ _ | z == nullPtr = E.throwIO ErrINVAL fopen_index z i flags = returnNotNull z =<< c'zip_fopen_index z (fromIntegral i) (combine flags) -- | Close file in zip archive. fclose :: ZipFile -> IO () fclose zf = errorOrNothing =<< c'zip_fclose zf where errorOrNothing 0 = return () errorOrNothing e = E.throwIO (errFromCInt e) -- | Read from file in zip archive. fread :: ZipFile -> Int -> IO [Word8] fread zf count = allocaArray count $ \buf -> do rcount <- c'zip_fread zf (castPtr buf) (fromIntegral count) if rcount < 0 then E.throwIO ErrREAD else peekArray (fromIntegral rcount) buf -- High level Haskell wrappers -- | Open zip archive, do something, and close the archive. withZip :: String -- ^ /path/ of the file to open -> [OpenFlag] -- ^ open mode -> (Zip -> IO a) -- ^ action to do on zip arhive -> IO a withZip filename flags action = do z <- open filename flags result <- action z close z return result -- | Get names of the files in archive. getFiles :: Zip -> [FileFlag] -> IO [String] getFiles z flags = do n <- get_num_files z mapM (\i -> get_name z i flags) [0..(n-1)] -- | Get size of the file in archive. getFileSize :: Zip -- ^ zip archive -> String -- ^ name of the file in the archive -> [FileFlag] -- ^ file name mode -> IO Int getFileSize z name flags = withCString name $ \name' -> alloca $ \stat -> do ret <- c'zip_stat z name' (combine flags) stat if ret /= 0 then E.throwIO =<< get_error z else return . fromIntegral . c'zip_stat'size =<< peek stat -- | Read uncompressed file from the archive. Produce a strict ByteString. readZipFile :: Zip -- ^ zip archive -> String -- ^ name of the file in the archive -> [FileFlag] -- ^ file name mode -> IO B.ByteString readZipFile z fname flags = return . B.pack =<< readZipFile' z fname flags -- | Read uncompressed file from the archive. Produce a list of 'Word8'. readZipFile' :: Zip -- ^ zip archive -> String -- ^ name of the file in the archive -> [FileFlag] -- ^ file name mode -> IO [Word8] readZipFile' z fname flags = do sz <- getFileSize z fname flags readZipFileHead' z fname flags sz -- | Read beginning of the uncompressed file from the archive. Produce a list of 'Word8'. readZipFileHead' :: Zip -- ^ zip archive -> String -- ^ name of the file in the archive -> [FileFlag] -- ^ file name mode -> Int -- ^ how many bytes to read -> IO [Word8] readZipFileHead' z fname flags n = do f <- fopen z fname flags bytes <- fread f n fclose f return bytes -- | Read beginning of the uncompressed file from the archive. Produce a strict ByteString. readZipFileHead :: Zip -- ^ zip archive -> String -- ^ name of the file in the archive -> [FileFlag] -- ^ file name mode -> Int -- ^ how many bytes to read -> IO B.ByteString readZipFileHead z fname flags n = return . B.pack =<< readZipFileHead' z fname flags n -- | Return True if path is a file name, not a directory name (does not end with '/'). isFile :: String -> Bool isFile filename = (lastMay filename /= Just '/') -- | Return True if path is a directory name (ends with '/'). isDir :: String -> Bool isDir = not . isFile lastMay :: [a] -> Maybe a lastMay [] = Nothing lastMay xs = Just $ last xs -- Return the second argument or throw the last libzip error. returnNotNull :: Zip -> Ptr a -> IO (Ptr a) returnNotNull z _ | z == nullPtr = E.throwIO ErrINVAL returnNotNull z ptr = if ptr /= nullPtr then return ptr else E.throwIO =<< get_error z