Take space that will be used by running downloads into account when checking annex.diskreserve.

This commit is contained in:
Joey Hess 2015-05-12 15:19:08 -04:00
parent 5935578ed2
commit a812d598ef
6 changed files with 55 additions and 13 deletions

View file

@ -41,6 +41,7 @@ import System.IO.Unsafe (unsafeInterleaveIO)
import Common.Annex import Common.Annex
import Logs.Location import Logs.Location
import Logs.Transfer
import qualified Git import qualified Git
import qualified Annex import qualified Annex
import qualified Annex.Queue import qualified Annex.Queue
@ -239,7 +240,7 @@ prepGetViaTmpChecked key unabletoget getkey = do
alreadythere <- liftIO $ if e alreadythere <- liftIO $ if e
then getFileSize tmp then getFileSize tmp
else return 0 else return 0
ifM (checkDiskSpace Nothing key alreadythere) ifM (checkDiskSpace Nothing key alreadythere True)
( do ( do
-- The tmp file may not have been left writable -- The tmp file may not have been left writable
when e $ thawContent tmp when e $ thawContent tmp
@ -278,18 +279,34 @@ withTmp key action = do
return res return res
{- Checks that there is disk space available to store a given key, {- Checks that there is disk space available to store a given key,
- in a destination (or the annex) printing a warning if not. -} - in a destination (or the annex) printing a warning if not.
checkDiskSpace :: Maybe FilePath -> Key -> Integer -> Annex Bool -
checkDiskSpace destination key alreadythere = ifM (Annex.getState Annex.force) - If the destination is on the same filesystem as the annex,
- checks for any other running downloads, removing the amount of data still
- to be downloaded from the free space. This way, we avoid overcommitting
- when doing concurrent downloads.
-}
checkDiskSpace :: Maybe FilePath -> Key -> Integer -> Bool -> Annex Bool
checkDiskSpace destination key alreadythere samefilesystem = ifM (Annex.getState Annex.force)
( return True ( return True
, do , do
reserve <- annexDiskReserve <$> Annex.getGitConfig -- We can't get inprogress and free at the same
-- time, and both can be changing, so there's a
-- small race here. Err on the side of caution
-- by getting inprogress first, so if it takes
-- a while, we'll see any decrease in the free
-- disk space.
inprogress <- if samefilesystem
then sizeOfDownloadsInProgress (/= key)
else pure 0
free <- liftIO . getDiskFree =<< dir free <- liftIO . getDiskFree =<< dir
case (free, fromMaybe 1 (keySize key)) of case (free, fromMaybe 1 (keySize key)) of
(Just have, need) -> do (Just have, need) -> do
let ok = (need + reserve <= have + alreadythere) reserve <- annexDiskReserve <$> Annex.getGitConfig
let delta = need + reserve - have - alreadythere + inprogress
let ok = delta <= 0
unless ok $ unless ok $
needmorespace (need + reserve - have - alreadythere) needmorespace delta
return ok return ok
_ -> return True _ -> return True
) )

View file

@ -135,7 +135,7 @@ performRemote key file backend numcopies remote =
let cleanup = liftIO $ catchIO (removeFile tmp) (const noop) let cleanup = liftIO $ catchIO (removeFile tmp) (const noop)
cleanup cleanup
cleanup `after` a tmp cleanup `after` a tmp
getfile tmp = ifM (checkDiskSpace (Just tmp) key 0) getfile tmp = ifM (checkDiskSpace (Just tmp) key 0 True)
( ifM (Remote.retrieveKeyFileCheap remote key (Just file) tmp) ( ifM (Remote.retrieveKeyFileCheap remote key (Just file) tmp)
( return (Just True) ( return (Just True)
, ifM (Annex.getState Annex.fast) , ifM (Annex.getState Annex.fast)

View file

@ -43,7 +43,7 @@ start file key = do
) )
perform :: FilePath -> Key -> CommandPerform perform :: FilePath -> Key -> CommandPerform
perform dest key = ifM (checkDiskSpace Nothing key 0) perform dest key = ifM (checkDiskSpace Nothing key 0 True)
( do ( do
src <- calcRepo $ gitAnnexLocation key src <- calcRepo $ gitAnnexLocation key
tmpdest <- fromRepo $ gitAnnexTmpObjectLocation key tmpdest <- fromRepo $ gitAnnexTmpObjectLocation key

View file

@ -147,16 +147,32 @@ checkTransfer t = do
{- Gets all currently running transfers. -} {- Gets all currently running transfers. -}
getTransfers :: Annex [(Transfer, TransferInfo)] getTransfers :: Annex [(Transfer, TransferInfo)]
getTransfers = do getTransfers = getTransfers' [Download, Upload]
getTransfers' :: [Direction] -> Annex [(Transfer, TransferInfo)]
getTransfers' dirs = do
transfers <- mapMaybe parseTransferFile . concat <$> findfiles transfers <- mapMaybe parseTransferFile . concat <$> findfiles
infos <- mapM checkTransfer transfers infos <- mapM checkTransfer transfers
return $ map (\(t, Just i) -> (t, i)) $ return $ map (\(t, Just i) -> (t, i)) $
filter running $ zip transfers infos filter running $ zip transfers infos
where where
findfiles = liftIO . mapM dirContentsRecursive findfiles = liftIO . mapM dirContentsRecursive
=<< mapM (fromRepo . transferDir) [Download, Upload] =<< mapM (fromRepo . transferDir) dirs
running (_, i) = isJust i running (_, i) = isJust i
{- Number of bytes remaining to download from matching downloads that are in
- progress. -}
sizeOfDownloadsInProgress :: (Key -> Bool) -> Annex Integer
sizeOfDownloadsInProgress match = sum . map remaining . filter wanted
<$> getTransfers' [Download]
where
wanted (t, _) = match (transferKey t)
remaining (t, info) =
case (keySize (transferKey t), bytesComplete info) of
(Just sz, Just done) -> sz - done
(Just sz, Nothing) -> sz
(Nothing, _) -> 0
{- Gets failed transfers for a given remote UUID. -} {- Gets failed transfers for a given remote UUID. -}
getFailedTransfers :: UUID -> Annex [(Transfer, TransferInfo)] getFailedTransfers :: UUID -> Annex [(Transfer, TransferInfo)]
getFailedTransfers u = catMaybes <$> (liftIO . getpairs =<< concat <$> findfiles) getFailedTransfers u = catMaybes <$> (liftIO . getpairs =<< concat <$> findfiles)

View file

@ -118,9 +118,16 @@ tmpDir d k = addTrailingPathSeparator $ d </> "tmp" </> keyFile k
{- Check if there is enough free disk space in the remote's directory to {- Check if there is enough free disk space in the remote's directory to
- store the key. Note that the unencrypted key size is checked. -} - store the key. Note that the unencrypted key size is checked. -}
prepareStore :: FilePath -> ChunkConfig -> Preparer Storer prepareStore :: FilePath -> ChunkConfig -> Preparer Storer
prepareStore d chunkconfig = checkPrepare prepareStore d chunkconfig = checkPrepare checker
(\k -> checkDiskSpace (Just d) k 0)
(byteStorer $ store d chunkconfig) (byteStorer $ store d chunkconfig)
where
checker k = do
annexdir <- fromRepo gitAnnexObjectDir
samefilesystem <- liftIO $ catchDefaultIO False $
(\a b -> deviceID a == deviceID b)
<$> getFileStatus d
<*> getFileStatus annexdir
checkDiskSpace (Just d) k 0 samefilesystem
store :: FilePath -> ChunkConfig -> Key -> L.ByteString -> MeterUpdate -> Annex Bool store :: FilePath -> ChunkConfig -> Key -> L.ByteString -> MeterUpdate -> Annex Bool
store d chunkconfig k b p = liftIO $ do store d chunkconfig k b p = liftIO $ do

2
debian/changelog vendored
View file

@ -10,6 +10,8 @@ git-annex (5.20150508.2) UNRELEASED; urgency=medium
However, progress bars are not yet displayed for concurrent transfers, However, progress bars are not yet displayed for concurrent transfers,
pending an updated version of the ascii-progress library. pending an updated version of the ascii-progress library.
* --quiet now makes progress output by rsync, wget, etc be quiet too. * --quiet now makes progress output by rsync, wget, etc be quiet too.
* Take space that will be used by running downloads into account when
checking annex.diskreserve.
-- Joey Hess <id@joeyh.name> Mon, 11 May 2015 12:45:06 -0400 -- Joey Hess <id@joeyh.name> Mon, 11 May 2015 12:45:06 -0400