module Darcs.Repository.Packs
( fetchAndUnpackBasic
, fetchAndUnpackPatches
, packsDir
, createPacks
) where
import qualified Codec.Archive.Tar as Tar
import Codec.Archive.Tar.Entry ( fileEntry, toTarPath )
import Codec.Compression.GZip as GZ ( compress, decompress )
import Control.Concurrent.Async ( withAsync )
import Control.Exception ( Exception, IOException, throwIO, catch, finally )
import Control.Monad ( void, when, unless )
import System.IO.Error ( isAlreadyExistsError )
import System.IO.Unsafe ( unsafeInterleaveIO )
import qualified Data.ByteString.Lazy.Char8 as BLC
import Data.List ( isPrefixOf, sort )
import System.Directory ( createDirectoryIfMissing
, renameFile
, removeFile
, doesFileExist
, getModificationTime
, listDirectory
)
import System.FilePath ( (</>)
, (<.>)
, takeFileName
, splitPath
, joinPath
, takeDirectory
)
import System.Posix.Files ( createLink )
import Darcs.Prelude
import Darcs.Util.ByteString ( gzReadFilePS )
import Darcs.Util.Lock ( withTemp )
import Darcs.Util.External ( Cachable(..), fetchFileLazyPS )
import Darcs.Util.Global ( darcsdir )
import Darcs.Util.Progress ( debugMessage, progressList )
import Darcs.Patch ( IsRepoType, RepoPatch )
import Darcs.Patch.PatchInfoAnd ( extractHash )
import Darcs.Patch.Progress ( progressFL )
import Darcs.Patch.Witnesses.Ordered ( mapFL )
import Darcs.Patch.Set ( patchSet2FL )
import Darcs.Repository.Traverse ( listInventories )
import Darcs.Repository.InternalTypes ( Repository )
import Darcs.Repository.Hashed ( readRepo )
import Darcs.Repository.Inventory ( getValidHash )
import Darcs.Repository.Format
( identifyRepoFormat, formatHas, RepoProperty ( HashedInventory ) )
import Darcs.Repository.Cache ( fetchFileUsingCache
, HashedDir(..)
, Cache
, closestWritableDirectory
, hashedDir
, bucketFolder
)
import Darcs.Repository.Old ( oldRepoFailMsg )
import Darcs.Repository.Pristine ( readHashedPristineRoot )
packsDir, basicPack, patchesPack :: String
packsDir = "packs"
basicPack = "basic.tar.gz"
patchesPack = "patches.tar.gz"
fetchAndUnpack :: FilePath
-> HashedDir
-> Cache
-> FilePath
-> IO ()
fetchAndUnpack filename dir cache remote = do
unpackTar cache dir . Tar.read . GZ.decompress =<<
fetchFileLazyPS (remote </> darcsdir </> packsDir </> filename) Uncachable
fetchAndUnpackPatches :: [String] -> Cache -> FilePath -> IO ()
fetchAndUnpackPatches paths cache remote =
withAsync (fetchAndUnpack patchesPack HashedInventoriesDir cache remote) $ \_ -> do
fetchFilesUsingCache cache HashedPatchesDir paths
fetchAndUnpackBasic :: Cache -> FilePath -> IO ()
fetchAndUnpackBasic = fetchAndUnpack basicPack HashedPristineDir
unpackTar :: Exception e => Cache -> HashedDir -> Tar.Entries e -> IO ()
unpackTar _ _ Tar.Done = return ()
unpackTar _ _ (Tar.Fail e) = throwIO e
unpackTar c dir (Tar.Next e es) = case Tar.entryContent e of
Tar.NormalFile bs _ -> do
let p = Tar.entryPath e
if "meta-" `isPrefixOf` takeFileName p
then unpackTar c dir es
else do
ex <- doesFileExist p
if ex
then debugMessage $ "TAR thread: exists " ++ p ++ "\nStopping TAR thread."
else do
if p == darcsdir </> "hashed_inventory"
then writeFile' Nothing p bs
else writeFile' (closestWritableDirectory c) p $ GZ.compress bs
debugMessage $ "TAR thread: GET " ++ p
unpackTar c dir es
_ -> fail "Unexpected non-file tar entry"
where
writeFile' Nothing path content = withTemp $ \tmp -> do
BLC.writeFile tmp content
renameFile tmp path
writeFile' (Just ca) path content = do
let fileFullPath = case splitPath path of
_:hDir:hFile:_ -> joinPath [ca, hDir, bucketFolder hFile, hFile]
_ -> fail "Unexpected file path"
createDirectoryIfMissing True $ takeDirectory path
createLink fileFullPath path `catch` (\(ex :: IOException) -> do
if isAlreadyExistsError ex then
return ()
else
writeFile' Nothing path content)
fetchFilesUsingCache :: Cache -> HashedDir -> [FilePath] -> IO ()
fetchFilesUsingCache cache dir = mapM_ go where
go path = do
ex <- doesFileExist $ darcsdir </> hashedDir dir </> path
if ex
then debugMessage $ "FILE thread: exists " ++ path
else void $ fetchFileUsingCache cache dir path
createPacks :: (IsRepoType rt, RepoPatch p)
=> Repository rt p wR wU wT -> IO ()
createPacks repo = flip finally (mapM_ removeFileIfExists
[ darcsdir </> "meta-filelist-inventories"
, darcsdir </> "meta-filelist-pristine"
, basicTar <.> "part"
, patchesTar <.> "part"
]) $ do
rf <- identifyRepoFormat "."
unless (formatHas HashedInventory rf) $ fail oldRepoFailMsg
createDirectoryIfMissing False (darcsdir </> packsDir)
Just hash <- readHashedPristineRoot repo
writeFile ( darcsdir </> packsDir </> "pristine" ) $ getValidHash hash
ps <- mapFL hashedPatchFileName . progressFL "Packing patches" . patchSet2FL <$> readRepo repo
is <- map ((darcsdir </> "inventories") </>) <$> listInventories
writeFile (darcsdir </> "meta-filelist-inventories") . unlines $
map takeFileName is
BLC.writeFile (patchesTar <.> "part") . GZ.compress . Tar.write =<<
mapM fileEntry' ((darcsdir </> "meta-filelist-inventories") : ps ++ reverse is)
renameFile (patchesTar <.> "part") patchesTar
pr <- sortByMTime =<< dirContents (darcsdir </> "pristine.hashed")
writeFile (darcsdir </> "meta-filelist-pristine") . unlines $
map takeFileName pr
BLC.writeFile (basicTar <.> "part") . GZ.compress . Tar.write =<< mapM fileEntry' (
[ darcsdir </> "meta-filelist-pristine"
, darcsdir </> "hashed_inventory"
] ++ progressList "Packing pristine" (reverse pr))
renameFile (basicTar <.> "part") basicTar
where
basicTar = darcsdir </> packsDir </> basicPack
patchesTar = darcsdir </> packsDir </> patchesPack
fileEntry' x = unsafeInterleaveIO $ do
content <- BLC.fromChunks . return <$> gzReadFilePS x
tp <- either fail return $ toTarPath False x
return $ fileEntry tp content
dirContents dir = map (dir </>) <$> listDirectory dir
hashedPatchFileName x = case extractHash x of
Left _ -> fail "unexpected unhashed patch"
Right h -> darcsdir </> "patches" </> h
sortByMTime xs = map snd . sort <$> mapM (\x -> (\t -> (t, x)) <$>
getModificationTime x) xs
removeFileIfExists x = do
ex <- doesFileExist x
when ex $ removeFile x