module Main where import Control.Monad (forM_) import System.Directory (canonicalizePath) import System.Environment (getArgs) import IO (stderr, hPutStrLn) import qualified System.IO.UTF8 as U import Codec.Archive.LibZip import DB import Book -- title-info of the FB2 file is expected to be found within first 8 kbytes. fbHeadSize :: Int fbHeadSize = 8*1024 main :: IO () main = do db <- initDB args <- getArgs forM_ args $ \arg -> do catchZipError $ do zipfile <- canonicalizePath arg withZip zipfile [] $ \z -> do files <- getFiles z [] forM_ files $ \file -> do -- TODO: implement lazy reading in LibZip txt <- readZipFileHead' z file [] fbHeadSize sz <- getFileSize z file [] let info = let i = readBookInfo $ toString txt in i { archive = zipfile, path = file, size = sz } catchSql (insert file db info) $ \e -> putErr $ "DB error: " ++ file ++ ": " ++ (seErrorMsg e) $ \e -> putErr $ "Archive error: " ++ arg ++ ": " ++ (show e) where insert :: String -> Connection -> Book -> IO () insert fname db info = do withTransaction db $ \db' -> insertBook db' info U.putStrLn $ fname ++ ":" ++ (concat $ take 2 $ lines $ show info) putErr :: String -> IO () putErr msg = hPutStrLn stderr msg toString :: [Word8] -> String toString = map w2c where w2c = toEnum . fromEnum