2012-07-07 17:47:36 +00:00
|
|
|
{- git-annex transfer information files and lock files
|
2012-07-01 18:29:00 +00:00
|
|
|
-
|
2015-01-21 16:50:09 +00:00
|
|
|
- Copyright 2012 Joey Hess <id@joeyh.name>
|
2012-07-01 18:29:00 +00:00
|
|
|
-
|
|
|
|
- Licensed under the GNU GPL version 3 or higher.
|
|
|
|
-}
|
|
|
|
|
2013-05-11 20:03:00 +00:00
|
|
|
{-# LANGUAGE CPP #-}
|
|
|
|
|
2012-07-01 18:29:00 +00:00
|
|
|
module Logs.Transfer where
|
|
|
|
|
2016-08-03 16:37:12 +00:00
|
|
|
import Types.Transfer
|
2016-01-20 20:36:33 +00:00
|
|
|
import Annex.Common
|
2012-07-01 18:29:00 +00:00
|
|
|
import Annex.Perms
|
|
|
|
import qualified Git
|
2013-03-28 21:03:04 +00:00
|
|
|
import Utility.Metered
|
2012-07-27 15:47:34 +00:00
|
|
|
import Utility.Percentage
|
2014-02-11 19:22:08 +00:00
|
|
|
import Utility.PID
|
2015-11-12 22:05:45 +00:00
|
|
|
import Annex.LockPool
|
2015-05-10 18:45:55 +00:00
|
|
|
import Logs.TimeStamp
|
2012-07-01 18:29:00 +00:00
|
|
|
|
|
|
|
import Data.Time.Clock
|
2012-07-18 22:42:41 +00:00
|
|
|
import Data.Time.Clock.POSIX
|
|
|
|
import Control.Concurrent
|
2012-07-01 18:29:00 +00:00
|
|
|
|
2012-08-08 20:06:01 +00:00
|
|
|
showLcDirection :: Direction -> String
|
|
|
|
showLcDirection Upload = "upload"
|
|
|
|
showLcDirection Download = "download"
|
2012-07-01 18:29:00 +00:00
|
|
|
|
2012-08-08 20:06:01 +00:00
|
|
|
readLcDirection :: String -> Maybe Direction
|
|
|
|
readLcDirection "upload" = Just Upload
|
|
|
|
readLcDirection "download" = Just Download
|
|
|
|
readLcDirection _ = Nothing
|
2012-07-01 18:29:00 +00:00
|
|
|
|
2013-03-01 19:23:59 +00:00
|
|
|
describeTransfer :: Transfer -> TransferInfo -> String
|
|
|
|
describeTransfer t info = unwords
|
|
|
|
[ show $ transferDirection t
|
|
|
|
, show $ transferUUID t
|
|
|
|
, fromMaybe (key2file $ transferKey t) (associatedFile info)
|
2013-04-02 20:38:47 +00:00
|
|
|
, show $ bytesComplete info
|
2013-03-01 19:23:59 +00:00
|
|
|
]
|
|
|
|
|
2012-08-29 19:24:09 +00:00
|
|
|
{- Transfers that will accomplish the same task. -}
|
|
|
|
equivilantTransfer :: Transfer -> Transfer -> Bool
|
|
|
|
equivilantTransfer t1 t2
|
|
|
|
| transferDirection t1 == Download && transferDirection t2 == Download &&
|
2012-08-29 19:32:57 +00:00
|
|
|
transferKey t1 == transferKey t2 = True
|
2012-08-29 19:24:09 +00:00
|
|
|
| otherwise = t1 == t2
|
|
|
|
|
2012-07-27 15:47:34 +00:00
|
|
|
percentComplete :: Transfer -> TransferInfo -> Maybe Percentage
|
2012-08-28 18:31:30 +00:00
|
|
|
percentComplete (Transfer { transferKey = key }) info =
|
|
|
|
percentage <$> keySize key <*> Just (fromMaybe 0 $ bytesComplete info)
|
2012-07-27 15:47:34 +00:00
|
|
|
|
2012-09-21 20:23:25 +00:00
|
|
|
{- Generates a callback that can be called as transfer progresses to update
|
2012-09-24 17:16:50 +00:00
|
|
|
- the transfer info file. Also returns the file it'll be updating, and a
|
|
|
|
- MVar that can be used to read the number of bytesComplete. -}
|
|
|
|
mkProgressUpdater :: Transfer -> TransferInfo -> Annex (MeterUpdate, FilePath, MVar Integer)
|
2012-09-21 20:23:25 +00:00
|
|
|
mkProgressUpdater t info = do
|
|
|
|
tfile <- fromRepo $ transferFile t
|
unify exception handling into Utility.Exception
Removed old extensible-exceptions, only needed for very old ghc.
Made webdav use Utility.Exception, to work after some changes in DAV's
exception handling.
Removed Annex.Exception. Mostly this was trivial, but note that
tryAnnex is replaced with tryNonAsync and catchAnnex replaced with
catchNonAsync. In theory that could be a behavior change, since the former
caught all exceptions, and the latter don't catch async exceptions.
However, in practice, nothing in the Annex monad uses async exceptions.
Grepping for throwTo and killThread only find stuff in the assistant,
which does not seem related.
Command.Add.undo is changed to accept a SomeException, and things
that use it for rollback now catch non-async exceptions, rather than
only IOExceptions.
2014-08-08 01:55:44 +00:00
|
|
|
_ <- tryNonAsync $ createAnnexDirectory $ takeDirectory tfile
|
2012-09-21 20:23:25 +00:00
|
|
|
mvar <- liftIO $ newMVar 0
|
2012-09-24 17:16:50 +00:00
|
|
|
return (liftIO . updater tfile mvar, tfile, mvar)
|
2012-11-11 04:51:07 +00:00
|
|
|
where
|
2013-03-28 21:03:04 +00:00
|
|
|
updater tfile mvar b = modifyMVar_ mvar $ \oldbytes -> do
|
|
|
|
let newbytes = fromBytesProcessed b
|
2013-04-03 07:52:41 +00:00
|
|
|
if newbytes - oldbytes >= mindelta
|
2012-11-11 04:51:07 +00:00
|
|
|
then do
|
2013-03-28 21:03:04 +00:00
|
|
|
let info' = info { bytesComplete = Just newbytes }
|
2012-11-11 04:51:07 +00:00
|
|
|
_ <- tryIO $ writeTransferInfoFile info' tfile
|
2013-03-28 21:03:04 +00:00
|
|
|
return newbytes
|
2012-11-11 04:51:07 +00:00
|
|
|
else return oldbytes
|
|
|
|
{- The minimum change in bytesComplete that is worth
|
|
|
|
- updating a transfer info file for is 1% of the total
|
|
|
|
- keySize, rounded down. -}
|
|
|
|
mindelta = case keySize (transferKey t) of
|
|
|
|
Just sz -> sz `div` 100
|
|
|
|
Nothing -> 100 * 1024 -- arbitrarily, 100 kb
|
2012-07-01 18:29:00 +00:00
|
|
|
|
2012-09-21 20:23:25 +00:00
|
|
|
startTransferInfo :: Maybe FilePath -> IO TransferInfo
|
|
|
|
startTransferInfo file = TransferInfo
|
|
|
|
<$> (Just . utcTimeToPOSIXSeconds <$> getCurrentTime)
|
2013-12-11 04:15:10 +00:00
|
|
|
#ifndef mingw32_HOST_OS
|
2012-09-21 20:23:25 +00:00
|
|
|
<*> pure Nothing -- pid not stored in file, so omitted for speed
|
2013-12-11 04:15:10 +00:00
|
|
|
#else
|
2014-02-11 19:22:08 +00:00
|
|
|
<*> (Just <$> getPID)
|
2013-12-11 04:15:10 +00:00
|
|
|
#endif
|
2012-09-21 20:23:25 +00:00
|
|
|
<*> pure Nothing -- tid ditto
|
|
|
|
<*> pure Nothing -- not 0; transfer may be resuming
|
|
|
|
<*> pure Nothing
|
|
|
|
<*> pure file
|
|
|
|
<*> pure False
|
|
|
|
|
2015-05-13 00:11:23 +00:00
|
|
|
{- If a transfer is still running, returns its TransferInfo.
|
|
|
|
-
|
|
|
|
- If no transfer is running, attempts to clean up the stale
|
|
|
|
- lock and info files. This can happen if a transfer process was
|
|
|
|
- interrupted.
|
|
|
|
-}
|
2012-07-01 18:29:00 +00:00
|
|
|
checkTransfer :: Transfer -> Annex (Maybe TransferInfo)
|
2012-07-01 19:04:29 +00:00
|
|
|
checkTransfer t = do
|
|
|
|
tfile <- fromRepo $ transferFile t
|
2015-05-13 00:11:23 +00:00
|
|
|
let cleanstale = do
|
|
|
|
void $ tryIO $ removeFile tfile
|
|
|
|
void $ tryIO $ removeFile $ transferLockFile tfile
|
2013-08-02 16:27:32 +00:00
|
|
|
#ifndef mingw32_HOST_OS
|
2015-11-12 22:05:45 +00:00
|
|
|
let lck = transferLockFile tfile
|
|
|
|
v <- getLockStatus lck
|
|
|
|
case v of
|
|
|
|
StatusLockedBy pid -> liftIO $ catchDefaultIO Nothing $
|
|
|
|
readTransferInfoFile (Just pid) tfile
|
|
|
|
StatusNoLockFile -> return Nothing
|
|
|
|
StatusUnLocked -> do
|
|
|
|
-- Take a non-blocking lock while deleting
|
|
|
|
-- the stale lock file. Ignore failure
|
|
|
|
-- due to permissions problems, races, etc.
|
|
|
|
void $ tryIO $ do
|
|
|
|
r <- tryLockExclusive Nothing lck
|
|
|
|
case r of
|
|
|
|
Just lockhandle -> liftIO $ do
|
|
|
|
cleanstale
|
|
|
|
dropLock lockhandle
|
|
|
|
_ -> noop
|
|
|
|
return Nothing
|
2013-05-11 20:03:00 +00:00
|
|
|
#else
|
2014-01-28 18:17:14 +00:00
|
|
|
v <- liftIO $ lockShared $ transferLockFile tfile
|
|
|
|
liftIO $ case v of
|
|
|
|
Nothing -> catchDefaultIO Nothing $
|
2013-05-11 20:03:00 +00:00
|
|
|
readTransferInfoFile Nothing tfile
|
2014-01-28 18:17:14 +00:00
|
|
|
Just lockhandle -> do
|
|
|
|
dropLock lockhandle
|
2015-05-13 00:11:23 +00:00
|
|
|
cleanstale
|
2014-01-28 18:17:14 +00:00
|
|
|
return Nothing
|
2013-05-11 20:03:00 +00:00
|
|
|
#endif
|
2012-07-01 18:29:00 +00:00
|
|
|
|
|
|
|
{- Gets all currently running transfers. -}
|
|
|
|
getTransfers :: Annex [(Transfer, TransferInfo)]
|
2015-05-12 22:34:49 +00:00
|
|
|
getTransfers = getTransfers' [Download, Upload] (const True)
|
2015-05-12 19:19:08 +00:00
|
|
|
|
2015-05-12 22:34:49 +00:00
|
|
|
getTransfers' :: [Direction] -> (Key -> Bool) -> Annex [(Transfer, TransferInfo)]
|
|
|
|
getTransfers' dirs wanted = do
|
|
|
|
transfers <- filter (wanted . transferKey)
|
|
|
|
<$> mapMaybe parseTransferFile . concat <$> findfiles
|
2012-07-01 18:29:00 +00:00
|
|
|
infos <- mapM checkTransfer transfers
|
|
|
|
return $ map (\(t, Just i) -> (t, i)) $
|
|
|
|
filter running $ zip transfers infos
|
2012-11-11 04:51:07 +00:00
|
|
|
where
|
|
|
|
findfiles = liftIO . mapM dirContentsRecursive
|
2015-05-12 19:19:08 +00:00
|
|
|
=<< mapM (fromRepo . transferDir) dirs
|
2012-11-11 04:51:07 +00:00
|
|
|
running (_, i) = isJust i
|
2012-07-01 18:29:00 +00:00
|
|
|
|
2015-05-12 19:19:08 +00:00
|
|
|
{- Number of bytes remaining to download from matching downloads that are in
|
|
|
|
- progress. -}
|
|
|
|
sizeOfDownloadsInProgress :: (Key -> Bool) -> Annex Integer
|
2015-05-12 22:34:49 +00:00
|
|
|
sizeOfDownloadsInProgress wanted = sum . map remaining
|
|
|
|
<$> getTransfers' [Download] wanted
|
2015-05-12 19:19:08 +00:00
|
|
|
where
|
|
|
|
remaining (t, info) =
|
|
|
|
case (keySize (transferKey t), bytesComplete info) of
|
|
|
|
(Just sz, Just done) -> sz - done
|
|
|
|
(Just sz, Nothing) -> sz
|
|
|
|
(Nothing, _) -> 0
|
|
|
|
|
2012-08-23 19:22:23 +00:00
|
|
|
{- Gets failed transfers for a given remote UUID. -}
|
|
|
|
getFailedTransfers :: UUID -> Annex [(Transfer, TransferInfo)]
|
|
|
|
getFailedTransfers u = catMaybes <$> (liftIO . getpairs =<< concat <$> findfiles)
|
2012-11-11 04:51:07 +00:00
|
|
|
where
|
|
|
|
getpairs = mapM $ \f -> do
|
|
|
|
let mt = parseTransferFile f
|
|
|
|
mi <- readTransferInfoFile Nothing f
|
|
|
|
return $ case (mt, mi) of
|
|
|
|
(Just t, Just i) -> Just (t, i)
|
|
|
|
_ -> Nothing
|
|
|
|
findfiles = liftIO . mapM dirContentsRecursive
|
|
|
|
=<< mapM (fromRepo . failedTransferDir u) [Download, Upload]
|
2012-08-23 19:22:23 +00:00
|
|
|
|
2013-09-25 15:46:17 +00:00
|
|
|
clearFailedTransfers :: UUID -> Annex [(Transfer, TransferInfo)]
|
|
|
|
clearFailedTransfers u = do
|
|
|
|
failed <- getFailedTransfers u
|
2013-09-26 03:19:01 +00:00
|
|
|
mapM_ (removeFailedTransfer . fst) failed
|
2013-09-25 15:46:17 +00:00
|
|
|
return failed
|
|
|
|
|
2012-09-17 18:58:43 +00:00
|
|
|
removeFailedTransfer :: Transfer -> Annex ()
|
|
|
|
removeFailedTransfer t = do
|
|
|
|
f <- fromRepo $ failedTransferFile t
|
|
|
|
liftIO $ void $ tryIO $ removeFile f
|
|
|
|
|
2013-03-19 00:34:56 +00:00
|
|
|
recordFailedTransfer :: Transfer -> TransferInfo -> Annex ()
|
|
|
|
recordFailedTransfer t info = do
|
|
|
|
failedtfile <- fromRepo $ failedTransferFile t
|
|
|
|
createAnnexDirectory $ takeDirectory failedtfile
|
|
|
|
liftIO $ writeTransferInfoFile info failedtfile
|
|
|
|
|
2012-07-01 18:29:00 +00:00
|
|
|
{- The transfer information file to use for a given Transfer. -}
|
|
|
|
transferFile :: Transfer -> Git.Repo -> FilePath
|
2012-08-23 17:42:13 +00:00
|
|
|
transferFile (Transfer direction u key) r = transferDir direction r
|
2012-09-21 20:23:25 +00:00
|
|
|
</> filter (/= '/') (fromUUID u)
|
2012-07-01 19:04:29 +00:00
|
|
|
</> keyFile key
|
2012-07-01 18:29:00 +00:00
|
|
|
|
2012-08-23 19:22:23 +00:00
|
|
|
{- The transfer information file to use to record a failed Transfer -}
|
|
|
|
failedTransferFile :: Transfer -> Git.Repo -> FilePath
|
|
|
|
failedTransferFile (Transfer direction u key) r = failedTransferDir u direction r
|
|
|
|
</> keyFile key
|
|
|
|
|
2012-07-07 17:47:36 +00:00
|
|
|
{- The transfer lock file corresponding to a given transfer info file. -}
|
|
|
|
transferLockFile :: FilePath -> FilePath
|
2012-07-17 21:22:00 +00:00
|
|
|
transferLockFile infofile = let (d,f) = splitFileName infofile in
|
|
|
|
combine d ("lck." ++ f)
|
2012-07-07 17:47:36 +00:00
|
|
|
|
2012-07-01 18:29:00 +00:00
|
|
|
{- Parses a transfer information filename to a Transfer. -}
|
2012-07-01 20:59:54 +00:00
|
|
|
parseTransferFile :: FilePath -> Maybe Transfer
|
2012-07-17 21:26:53 +00:00
|
|
|
parseTransferFile file
|
2013-04-03 07:52:41 +00:00
|
|
|
| "lck." `isPrefixOf` takeFileName file = Nothing
|
2012-07-17 21:26:53 +00:00
|
|
|
| otherwise = case drop (length bits - 3) bits of
|
2012-07-01 19:04:29 +00:00
|
|
|
[direction, u, key] -> Transfer
|
2012-08-08 20:06:01 +00:00
|
|
|
<$> readLcDirection direction
|
2012-07-01 20:59:54 +00:00
|
|
|
<*> pure (toUUID u)
|
2012-07-01 18:29:00 +00:00
|
|
|
<*> fileKey key
|
|
|
|
_ -> Nothing
|
2012-11-11 04:51:07 +00:00
|
|
|
where
|
|
|
|
bits = splitDirectories file
|
2012-07-01 18:29:00 +00:00
|
|
|
|
2012-09-16 05:53:06 +00:00
|
|
|
writeTransferInfoFile :: TransferInfo -> FilePath -> IO ()
|
2014-02-03 14:16:05 +00:00
|
|
|
writeTransferInfoFile info tfile = writeFileAnyEncoding tfile $
|
|
|
|
writeTransferInfo info
|
2012-09-16 05:53:06 +00:00
|
|
|
|
2012-09-19 20:08:37 +00:00
|
|
|
{- File format is a header line containing the startedTime and any
|
|
|
|
- bytesComplete value. Followed by a newline and the associatedFile.
|
|
|
|
-
|
2013-12-11 04:15:10 +00:00
|
|
|
- On unix, the transferPid is not included; instead it is obtained
|
|
|
|
- by looking at the process that locks the file.
|
|
|
|
-
|
|
|
|
- On windows, the transferPid is included, as a second line.
|
2012-09-19 20:08:37 +00:00
|
|
|
-}
|
2012-07-01 18:29:00 +00:00
|
|
|
writeTransferInfo :: TransferInfo -> String
|
2012-07-01 19:04:29 +00:00
|
|
|
writeTransferInfo info = unlines
|
2012-09-19 20:08:37 +00:00
|
|
|
[ (maybe "" show $ startedTime info) ++
|
2013-04-03 07:52:41 +00:00
|
|
|
(maybe "" (\b -> ' ' : show b) (bytesComplete info))
|
2013-12-11 04:15:10 +00:00
|
|
|
#ifdef mingw32_HOST_OS
|
|
|
|
, maybe "" show (transferPid info)
|
|
|
|
#endif
|
2012-07-01 19:04:29 +00:00
|
|
|
, fromMaybe "" $ associatedFile info -- comes last; arbitrary content
|
2012-07-01 18:29:00 +00:00
|
|
|
]
|
|
|
|
|
2013-12-11 03:32:10 +00:00
|
|
|
readTransferInfoFile :: Maybe PID -> FilePath -> IO (Maybe TransferInfo)
|
2014-02-03 14:16:05 +00:00
|
|
|
readTransferInfoFile mpid tfile = catchDefaultIO Nothing $
|
|
|
|
readTransferInfo mpid <$> readFileStrictAnyEncoding tfile
|
2012-09-16 05:53:06 +00:00
|
|
|
|
2013-12-11 03:32:10 +00:00
|
|
|
readTransferInfo :: Maybe PID -> String -> Maybe TransferInfo
|
2012-09-19 20:08:37 +00:00
|
|
|
readTransferInfo mpid s = TransferInfo
|
|
|
|
<$> time
|
2013-12-11 04:15:10 +00:00
|
|
|
#ifdef mingw32_HOST_OS
|
2013-12-11 04:18:58 +00:00
|
|
|
<*> pure (if isJust mpid then mpid else mpid')
|
2013-12-11 04:15:10 +00:00
|
|
|
#else
|
2012-09-19 20:08:37 +00:00
|
|
|
<*> pure mpid
|
2013-12-11 04:15:10 +00:00
|
|
|
#endif
|
2012-09-19 20:08:37 +00:00
|
|
|
<*> pure Nothing
|
|
|
|
<*> pure Nothing
|
|
|
|
<*> bytes
|
|
|
|
<*> pure (if null filename then Nothing else Just filename)
|
|
|
|
<*> pure False
|
2012-11-11 04:51:07 +00:00
|
|
|
where
|
2013-12-11 04:15:10 +00:00
|
|
|
#ifdef mingw32_HOST_OS
|
2014-01-28 18:43:20 +00:00
|
|
|
(firstline, otherlines) = separate (== '\n') s
|
|
|
|
(secondline, rest) = separate (== '\n') otherlines
|
2013-12-11 04:15:10 +00:00
|
|
|
mpid' = readish secondline
|
|
|
|
#else
|
2012-12-19 18:16:58 +00:00
|
|
|
(firstline, rest) = separate (== '\n') s
|
2013-12-11 04:15:10 +00:00
|
|
|
#endif
|
2012-12-19 20:15:39 +00:00
|
|
|
filename
|
|
|
|
| end rest == "\n" = beginning rest
|
|
|
|
| otherwise = rest
|
2012-11-11 04:51:07 +00:00
|
|
|
bits = split " " firstline
|
|
|
|
numbits = length bits
|
|
|
|
time = if numbits > 0
|
|
|
|
then Just <$> parsePOSIXTime =<< headMaybe bits
|
|
|
|
else pure Nothing -- not failure
|
|
|
|
bytes = if numbits > 1
|
|
|
|
then Just <$> readish =<< headMaybe (drop 1 bits)
|
|
|
|
else pure Nothing -- not failure
|
2012-07-19 00:48:08 +00:00
|
|
|
|
2012-08-23 17:42:13 +00:00
|
|
|
{- The directory holding transfer information files for a given Direction. -}
|
|
|
|
transferDir :: Direction -> Git.Repo -> FilePath
|
|
|
|
transferDir direction r = gitAnnexTransferDir r </> showLcDirection direction
|
|
|
|
|
2012-08-23 19:22:23 +00:00
|
|
|
{- The directory holding failed transfer information files for a given
|
|
|
|
- Direction and UUID -}
|
|
|
|
failedTransferDir :: UUID -> Direction -> Git.Repo -> FilePath
|
|
|
|
failedTransferDir u direction r = gitAnnexTransferDir r
|
|
|
|
</> "failed"
|
|
|
|
</> showLcDirection direction
|
2012-09-21 20:23:25 +00:00
|
|
|
</> filter (/= '/') (fromUUID u)
|
2013-02-28 01:42:07 +00:00
|
|
|
|
|
|
|
prop_read_write_transferinfo :: TransferInfo -> Bool
|
|
|
|
prop_read_write_transferinfo info
|
2013-04-03 07:52:41 +00:00
|
|
|
| isJust (transferRemote info) = True -- remote not stored
|
|
|
|
| isJust (transferTid info) = True -- tid not stored
|
2013-02-28 01:42:07 +00:00
|
|
|
| otherwise = Just (info { transferPaused = False }) == info'
|
|
|
|
where
|
|
|
|
info' = readTransferInfo (transferPid info) (writeTransferInfo info)
|
|
|
|
|