module Darcs.Repository.Traverse
( cleanInventories
, cleanPatches
, cleanPristine
, cleanRepository
, diffHashLists
, listInventories
, listInventoriesLocal
, listInventoriesRepoDir
, listPatchesLocalBucketed
, specialPatches
) where
import Darcs.Prelude
import Data.Maybe ( fromJust )
import qualified Data.ByteString.Char8 as BC ( unpack, pack )
import qualified Data.Set as Set
import System.Directory ( listDirectory )
import System.FilePath.Posix( (</>) )
import Darcs.Repository.Cache ( HashedDir(..), bucketFolder )
import Darcs.Repository.HashedIO ( cleanHashdir )
import Darcs.Repository.Inventory
( Inventory(..)
, emptyInventory
, getValidHash
, inventoryPatchNames
, parseInventory
, peekPristineHash
, skipPristineHash
)
import Darcs.Repository.InternalTypes
( Repository
, repoCache
, withRepoLocation
)
import Darcs.Repository.Paths
( hashedInventory
, hashedInventoryPath
, inventoriesDir
, inventoriesDirPath
, patchesDirPath
)
import Darcs.Repository.Prefs ( globalCacheDir )
import Darcs.Util.ByteString ( gzReadFilePS )
import Darcs.Util.Exception ( ifDoesNotExistError )
import Darcs.Util.Global ( darcsdir, debugMessage )
import Darcs.Util.Lock ( removeFileMayNotExist )
cleanRepository :: Repository rt p wR wU wT -> IO ()
cleanRepository r = cleanPristine r >> cleanInventories r >> cleanPatches r
data DirLayout = PlainLayout | BucketedLayout
cleanPristine :: Repository rt p wR wU wT -> IO ()
cleanPristine r = withRepoLocation r $ do
debugMessage "Cleaning out the pristine cache..."
i <- gzReadFilePS hashedInventoryPath
cleanHashdir (repoCache r) HashedPristineDir [peekPristineHash i]
diffHashLists :: [String] -> [String] -> [String]
diffHashLists xs ys = from_set $ (to_set xs) `Set.difference` (to_set ys)
where
to_set = Set.fromList . map BC.pack
from_set = map BC.unpack . Set.toList
cleanInventories :: Repository rt p wR wU wT -> IO ()
cleanInventories _ = do
debugMessage "Cleaning out inventories..."
hs <- listInventoriesLocal
fs <- ifDoesNotExistError [] $ listDirectory inventoriesDirPath
mapM_ (removeFileMayNotExist . (inventoriesDirPath </>))
(diffHashLists fs hs)
specialPatches :: [FilePath]
specialPatches = ["unrevert", "pending", "pending.tentative"]
cleanPatches :: Repository rt p wR wU wT -> IO ()
cleanPatches _ = do
debugMessage "Cleaning out patches..."
hs <- (specialPatches ++) <$> listPatchesLocal PlainLayout darcsdir darcsdir
fs <- ifDoesNotExistError [] (listDirectory patchesDirPath)
mapM_ (removeFileMayNotExist . (patchesDirPath </>)) (diffHashLists fs hs)
listInventoriesWith
:: (FilePath -> IO Inventory)
-> DirLayout
-> String -> String -> IO [String]
listInventoriesWith readInv dirformat baseDir startDir = do
mbStartingWithInv <- getStartingWithHash startDir hashedInventory
followStartingWiths mbStartingWithInv
where
getStartingWithHash dir file = inventoryParent <$> readInv (dir </> file)
invDir = baseDir </> inventoriesDir
nextDir dir = case dirformat of
BucketedLayout -> invDir </> bucketFolder dir
PlainLayout -> invDir
followStartingWiths Nothing = return []
followStartingWiths (Just hash) = do
let startingWith = getValidHash hash
mbNextInv <- getStartingWithHash (nextDir startingWith) startingWith
(startingWith :) <$> followStartingWiths mbNextInv
listInventories :: IO [String]
listInventories =
listInventoriesWith readInventory PlainLayout darcsdir darcsdir
listInventoriesLocal :: IO [String]
listInventoriesLocal =
listInventoriesWith readInventoryLocal PlainLayout darcsdir darcsdir
listInventoriesRepoDir :: String -> IO [String]
listInventoriesRepoDir repoDir = do
gCacheDir' <- globalCacheDir
let gCacheInvDir = fromJust gCacheDir'
listInventoriesWith
readInventoryLocal
BucketedLayout
gCacheInvDir
(repoDir </> darcsdir)
listPatchesLocal :: DirLayout -> String -> String -> IO [String]
listPatchesLocal dirformat baseDir startDir = do
inventory <- readInventory (startDir </> hashedInventory)
followStartingWiths
(inventoryParent inventory)
(inventoryPatchNames inventory)
where
invDir = baseDir </> inventoriesDir
nextDir dir =
case dirformat of
BucketedLayout -> invDir </> bucketFolder dir
PlainLayout -> invDir
followStartingWiths Nothing patches = return patches
followStartingWiths (Just hash) patches = do
let startingWith = getValidHash hash
inv <- readInventoryLocal (nextDir startingWith </> startingWith)
(patches ++) <$>
followStartingWiths (inventoryParent inv) (inventoryPatchNames inv)
listPatchesLocalBucketed :: String -> String -> IO [String]
listPatchesLocalBucketed = listPatchesLocal BucketedLayout
readInventoryLocal :: FilePath -> IO Inventory
readInventoryLocal path =
ifDoesNotExistError emptyInventory $ readInventory path
readInventory :: FilePath -> IO Inventory
readInventory path = do
inv <- skipPristineHash <$> gzReadFilePS path
case parseInventory inv of
Right r -> return r
Left e -> fail $ unlines [unwords ["parse error in file", path], e]