module Darcs.Repository.Cache
( cacheHash
, okayHash
, takeHash
, Cache(..)
, CacheType(..)
, CacheLoc(..)
, WritableOrNot(..)
, HashedDir(..)
, hashedDir
, bucketFolder
, unionCaches
, unionRemoteCaches
, cleanCaches
, cleanCachesWithHint
, fetchFileUsingCache
, speculateFileUsingCache
, speculateFilesUsingCache
, writeFileUsingCache
, peekInCache
, repo2cache
, writable
, isThisRepo
, hashedFilePath
, allHashedDirs
, compareByLocality
, reportBadSources
) where
import Control.Monad ( liftM, when, guard, unless, filterM, forM_, mplus )
import qualified Data.ByteString as B (length, drop, ByteString )
import qualified Data.ByteString.Char8 as BC (unpack)
import Data.List ( nub, intercalate )
import Data.Maybe ( catMaybes, listToMaybe, fromMaybe )
import System.FilePath.Posix ( (</>), joinPath, dropFileName )
import System.Directory ( createDirectoryIfMissing, removeFile, doesFileExist,
doesDirectoryExist, getDirectoryContents,
getPermissions )
import qualified System.Directory as SD ( writable )
import System.IO ( hPutStrLn, stderr )
import System.Posix.Files ( createLink, linkCount, getSymbolicLinkStatus )
import Darcs.Util.ByteString ( gzWriteFilePS, linesPS )
import Darcs.Util.Global ( darcsdir, addBadSource, isBadSource, addReachableSource,
isReachableSource, getBadSourcesList, defaultRemoteDarcsCmd )
import Darcs.Util.External ( gzFetchFilePS, fetchFilePS
, speculateFileOrUrl, copyFileOrUrl
, Cachable( Cachable ) )
import Darcs.Repository.Flags ( Compression(..) )
import Darcs.Util.Lock ( writeAtomicFilePS, gzWriteAtomicFilePS,
withTemp )
import Darcs.Util.SignalHandler ( catchNonSignal )
import Darcs.Util.URL ( isValidLocalPath, isHttpUrl, isSshUrl )
import Darcs.Util.File ( withCurrentDirectory )
import Darcs.Util.Crypt.SHA1 ( sha1PS )
import Darcs.Util.Crypt.SHA256 ( sha256sum )
import Darcs.Util.English ( englishNum, Noun(..), Pronoun(..) )
import Darcs.Util.Exception ( catchall )
import Darcs.Util.Progress ( progressList, debugMessage, debugFail )
import qualified Darcs.Util.Download as Download ( ConnectionError(..) )
data HashedDir = HashedPristineDir
| HashedPatchesDir
| HashedInventoriesDir
hashedDir :: HashedDir -> String
hashedDir HashedPristineDir = "pristine.hashed"
hashedDir HashedPatchesDir = "patches"
hashedDir HashedInventoriesDir = "inventories"
allHashedDirs :: [HashedDir]
allHashedDirs = [ HashedPristineDir
, HashedPatchesDir
, HashedInventoriesDir
]
data WritableOrNot = Writable
| NotWritable
deriving ( Eq, Show )
data CacheType = Repo
| Directory
deriving ( Eq, Show )
data CacheLoc = Cache
{ cacheType :: !CacheType
, cacheWritable :: !WritableOrNot
, cacheSource :: !String
}
newtype Cache = Ca [CacheLoc]
instance Eq CacheLoc where
(Cache aTy _ aSrc) == (Cache bTy _ bSrc) = aTy == bTy && aSrc == bSrc
instance Show CacheLoc where
show (Cache Repo Writable a) = "thisrepo:" ++ a
show (Cache Repo NotWritable a) = "repo:" ++ a
show (Cache Directory Writable a) = "cache:" ++ a
show (Cache Directory NotWritable a) = "readonly:" ++ a
instance Show Cache where
show (Ca cs) = unlines $ map show cs
unionCaches :: Cache -> Cache -> Cache
unionCaches (Ca a) (Ca b) = Ca (nub (a ++ b))
unionRemoteCaches :: Cache -> Cache -> String -> IO Cache
unionRemoteCaches local (Ca remote) repourl
| isValidLocalPath repourl = do
f <- filtered
return $ local `unionCaches` Ca f
| otherwise = return local
where
filtered = catMaybes `fmap`
mapM (\x -> mbGetRemoteCacheLoc x `catchall` return Nothing) remote
mbGetRemoteCacheLoc :: CacheLoc -> IO (Maybe CacheLoc)
mbGetRemoteCacheLoc (Cache Repo Writable _) = return Nothing
mbGetRemoteCacheLoc c@(Cache t _ url)
| isValidLocalPath url = do
ex <- doesDirectoryExist url
if ex
then do
p <- getPermissions url
return $ Just $ if writable c && SD.writable p
then c
else Cache t NotWritable url
else return Nothing
| otherwise = return $ Just c
compareByLocality :: CacheLoc -> CacheLoc -> Ordering
compareByLocality (Cache _ w x) (Cache _ z y)
| isValidLocalPath x && isRemote y = LT
| isRemote x && isValidLocalPath y = GT
| isHttpUrl x && isSshUrl y = LT
| isSshUrl x && isHttpUrl y = GT
| isValidLocalPath x && isWritable w
&& isValidLocalPath y && isNotWritable z = LT
| otherwise = EQ
where
isRemote r = isHttpUrl r || isSshUrl r
isWritable = (==) Writable
isNotWritable = (==) NotWritable
repo2cache :: String -> Cache
repo2cache r = Ca [Cache Repo NotWritable r]
cacheHash :: B.ByteString -> String
cacheHash ps = if sizeStrLen > 10
then shaOfPs
else replicate (10 sizeStrLen) '0' ++ sizeStr
++ '-' : shaOfPs
where
sizeStr = show $ B.length ps
sizeStrLen = length sizeStr
shaOfPs = sha256sum ps
okayHash :: String -> Bool
okayHash s = length s `elem` [40, 64, 75]
takeHash :: B.ByteString -> Maybe (String, B.ByteString)
takeHash ps = do
h <- listToMaybe $ linesPS ps
let v = BC.unpack h
guard $ okayHash v
return (v, B.drop (B.length h) ps)
checkHash :: String -> B.ByteString -> Bool
checkHash h s
| length h == 40 = (show $ sha1PS s) == h
| length h == 64 = sha256sum s == h
| length h == 75 =
B.length s == read (take 10 h) && sha256sum s == drop 11 h
| otherwise = False
fetchFileUsingCache :: Cache -> HashedDir -> String
-> IO (String, B.ByteString)
fetchFileUsingCache = fetchFileUsingCachePrivate Anywhere
writable :: CacheLoc -> Bool
writable (Cache _ NotWritable _) = False
writable (Cache _ Writable _) = True
isThisRepo :: CacheLoc -> Bool
isThisRepo (Cache Repo Writable _) = True
isThisRepo _ = False
bucketFolder :: String -> String
bucketFolder f = take 2 (cleanHash f)
where
cleanHash fileName = case dropWhile (/= '-') fileName of
[] -> fileName
s -> drop 1 s
hashedFilePath :: CacheLoc -> HashedDir -> String -> String
hashedFilePath (Cache Directory _ d) s f =
joinPath [d, hashedDir s, bucketFolder f, f]
hashedFilePath (Cache Repo _ r) s f =
joinPath [r, darcsdir, hashedDir s, f]
hashedFilePathReadOnly :: CacheLoc -> HashedDir -> String -> String
hashedFilePathReadOnly (Cache Directory _ d) s f =
d ++ "/" ++ hashedDir s ++ "/" ++ f
hashedFilePathReadOnly (Cache Repo _ r) s f =
r ++ "/" ++ darcsdir ++ "/" ++ hashedDir s ++ "/" ++ f
peekInCache :: Cache -> HashedDir -> String -> IO Bool
peekInCache (Ca cache) subdir f = cacheHasIt cache `catchall` return False
where
cacheHasIt [] = return False
cacheHasIt (c : cs)
| not $ writable c = cacheHasIt cs
| otherwise = do
ex <- doesFileExist $ hashedFilePath c subdir f
if ex then return True else cacheHasIt cs
speculateFileUsingCache :: Cache -> HashedDir -> String -> IO ()
speculateFileUsingCache c sd h = do
debugMessage $ "Speculating on " ++ h
copyFileUsingCache OnlySpeculate c sd h
speculateFilesUsingCache :: Cache -> HashedDir -> [String] -> IO ()
speculateFilesUsingCache _ _ [] = return ()
speculateFilesUsingCache cache sd hs = do
debugMessage $ "Thinking about speculating on " ++ unwords hs
hs' <- filterM (fmap not . peekInCache cache sd) hs
unless (null hs') $ do
debugMessage $ "Speculating on " ++ unwords hs'
copyFilesUsingCache OnlySpeculate cache sd hs'
data OrOnlySpeculate = ActuallyCopy
| OnlySpeculate
deriving ( Eq )
copyFileUsingCache :: OrOnlySpeculate -> Cache -> HashedDir -> String -> IO ()
copyFileUsingCache oos (Ca cache) subdir f = do
debugMessage $
"I'm doing copyFileUsingCache on " ++ hashedDir subdir ++ "/" ++ f
Just stickItHere <- cacheLoc cache
createDirectoryIfMissing True
(reverse $ dropWhile (/= '/') $ reverse stickItHere)
debugMessage $ "Will effectively do copyFileUsingCache to: " ++ show stickItHere
filterBadSources cache >>= sfuc stickItHere
`catchall`
return ()
where
cacheLoc [] = return Nothing
cacheLoc (c : cs)
| not $ writable c = cacheLoc cs
| otherwise = do
let attemptPath = hashedFilePath c subdir f
ex <- doesFileExist attemptPath
if ex
then fail $ "File already present in writable location."
else do
othercache <- cacheLoc cs
return $ othercache `mplus` Just attemptPath
sfuc _ [] = return ()
sfuc out (c : cs)
| not (writable c) =
let cacheFile = hashedFilePathReadOnly c subdir f in
if oos == OnlySpeculate
then speculateFileOrUrl cacheFile out
`catchNonSignal`
\e -> checkCacheReachability (show e) c
else do debugMessage $ "Copying from " ++ show cacheFile ++ " to " ++ show out
copyFileOrUrl defaultRemoteDarcsCmd cacheFile out Cachable
`catchNonSignal`
(\e -> do checkCacheReachability (show e) c
sfuc out cs)
| otherwise = sfuc out cs
copyFilesUsingCache :: OrOnlySpeculate -> Cache -> HashedDir -> [String]
-> IO ()
copyFilesUsingCache oos cache subdir hs =
forM_ hs $ copyFileUsingCache oos cache subdir
data FromWhere = LocalOnly
| Anywhere
deriving ( Eq )
checkCacheReachability :: String -> CacheLoc -> IO ()
checkCacheReachability e cache
| isValidLocalPath source = doUnreachableCheck $
checkFileReachability (doesDirectoryExist source)
| isHttpUrl source =
doUnreachableCheck $ do
let err = case dropWhile (/= '(') e of
(_ : xs) -> fst (break (==')') xs)
_ -> e
case reads err :: [(Download.ConnectionError, String)] of
[(_, _)] -> addBadSource source
_ -> checkFileReachability
(checkHashedInventoryReachability cache)
| isSshUrl source = doUnreachableCheck $
checkFileReachability (checkHashedInventoryReachability cache)
| otherwise = fail $ "unknown transport protocol for: " ++ source
where
source = cacheSource cache
doUnreachableCheck unreachableAction = do
reachable <- isReachableSource
unless (reachable source) unreachableAction
checkFileReachability doCheck = do
reachable <- doCheck
if reachable
then addReachableSource source
else addBadSource source
filterBadSources :: [CacheLoc] -> IO [CacheLoc]
filterBadSources cache = do
badSource <- isBadSource
return $ filter (not . badSource . cacheSource) cache
checkHashedInventoryReachability :: CacheLoc -> IO Bool
checkHashedInventoryReachability cache = withTemp $ \tempout -> do
let f = cacheSource cache </> darcsdir </> "hashed_inventory"
copyFileOrUrl defaultRemoteDarcsCmd f tempout Cachable
return True
`catchNonSignal` const (return False)
fetchFileUsingCachePrivate :: FromWhere -> Cache -> HashedDir -> String
-> IO (String, B.ByteString)
fetchFileUsingCachePrivate fromWhere (Ca cache) subdir f = do
when (fromWhere == Anywhere) $
copyFileUsingCache ActuallyCopy (Ca cache) subdir f
filterBadSources cache >>= ffuc
`catchall` debugFail ("Couldn't fetch `" ++ f ++ "'\nin subdir "
++ hashedDir subdir ++ " from sources:\n\n"
++ show (Ca cache))
where
ffuc (c : cs)
| not (writable c) &&
(Anywhere == fromWhere || isValidLocalPath (hashedFilePathReadOnly c subdir f)) = do
let cacheFile = hashedFilePathReadOnly c subdir f
debugMessage $ "In fetchFileUsingCachePrivate I'm directly grabbing file contents from "
++ cacheFile
x <- gzFetchFilePS cacheFile Cachable
if not $ checkHash f x
then do
x' <- fetchFilePS cacheFile Cachable
unless (checkHash f x') $ do
hPutStrLn stderr $ "Hash failure in " ++ cacheFile
fail $ "Hash failure in " ++ cacheFile
return (cacheFile, x')
else return (cacheFile, x)
`catchNonSignal` \e -> do
checkCacheReachability (show e) c
filterBadSources cs >>= ffuc
| writable c = let cacheFile = hashedFilePath c subdir f in do
debugMessage $ "About to gzFetchFilePS from " ++ show cacheFile
x1 <- gzFetchFilePS cacheFile Cachable
debugMessage $ "gzFetchFilePS done."
x <- if not $ checkHash f x1
then do
x2 <- fetchFilePS cacheFile Cachable
unless (checkHash f x2) $ do
hPutStrLn stderr $ "Hash failure in " ++ cacheFile
removeFile cacheFile
fail $ "Hash failure in " ++ cacheFile
return x2
else return x1
mapM_ (tryLinking cacheFile) cs
return (cacheFile, x)
`catchNonSignal` \e -> do
debugMessage "Caught exception, now attempt creating cache."
createCache c subdir `catchall` return ()
checkCacheReachability (show e) c
(fname, x) <- filterBadSources cs >>= ffuc
debugMessage $ "Attempt creating link from: " ++ show fname ++ " to " ++ show cacheFile
(createLink fname cacheFile >> (debugMessage "successfully created link")
>> return (cacheFile, x))
`catchall` do
debugMessage $ "Attempt writing file: " ++ show cacheFile
do createDirectoryIfMissing True (dropFileName cacheFile)
gzWriteFilePS cacheFile x
debugMessage $ "successfully wrote file"
`catchall` return ()
return (fname, x)
| otherwise = ffuc cs
ffuc [] = debugFail $ "No sources from which to fetch file `" ++ f
++ "'\n"++ show (Ca cache)
tryLinking ff c@(Cache Directory Writable d) = do
createDirectoryIfMissing False (d ++ "/" ++ hashedDir subdir)
createLink ff (hashedFilePath c subdir f)
`catchall`
return ()
tryLinking _ _ = return ()
createCache :: CacheLoc -> HashedDir -> IO ()
createCache (Cache Directory _ d) subdir =
createDirectoryIfMissing True (d ++ "/" ++ hashedDir subdir)
createCache _ _ = return ()
write :: Compression -> String -> B.ByteString -> IO ()
write NoCompression = writeAtomicFilePS
write GzipCompression = gzWriteAtomicFilePS
writeFileUsingCache :: Cache -> Compression -> HashedDir -> B.ByteString
-> IO String
writeFileUsingCache (Ca cache) compr subdir ps = do
_ <- fetchFileUsingCachePrivate LocalOnly (Ca cache) subdir hash
return hash
`catchall`
wfuc cache
`catchall`
debugFail ("Couldn't write `" ++ hash ++ "'\nin subdir "
++ hashedDir subdir ++ " to sources:\n\n"++ show (Ca cache))
where
hash = cacheHash ps
wfuc (c : cs)
| not $ writable c = wfuc cs
| otherwise = do
createCache c subdir
write compr (hashedFilePath c subdir hash) ps
return hash
wfuc [] = debugFail $ "No location to write file `" ++ hashedDir subdir
++ "/" ++ hash ++ "'"
cleanCaches :: Cache -> HashedDir -> IO ()
cleanCaches c d = cleanCachesWithHint' c d Nothing
cleanCachesWithHint :: Cache -> HashedDir -> [String] -> IO ()
cleanCachesWithHint c d h = cleanCachesWithHint' c d (Just h)
cleanCachesWithHint' :: Cache -> HashedDir -> Maybe [String] -> IO ()
cleanCachesWithHint' (Ca cs) subdir hint = mapM_ cleanCache cs
where
cleanCache (Cache Directory Writable d) =
withCurrentDirectory (d ++ "/" ++ hashedDir subdir) (do
fs' <- getDirectoryContents "."
let fs = filter okayHash $ fromMaybe fs' hint
cleanMsg = "Cleaning cache " ++ d ++ "/" ++ hashedDir subdir
mapM_ clean $ progressList cleanMsg fs)
`catchall`
return ()
cleanCache _ = return ()
clean f = do
lc <- linkCount `liftM` getSymbolicLinkStatus f
when (lc < 2) $ removeFile f
`catchall`
return ()
reportBadSources :: IO ()
reportBadSources = do
sources <- getBadSourcesList
let size = length sources
unless (null sources) $ hPutStrLn stderr $
concat [ "\nHINT: I could not reach the following "
, englishNum size (Noun "repository") ":"
, "\n"
, intercalate "\n" (map (" " ++) sources)
, "\n If you're not using "
, englishNum size It ", you should probably delete"
, "\n the corresponding "
, englishNum size (Noun "entry") " from _darcs/prefs/sources."
]