pull in transfer log code from assistant branch
New log file format.
This commit is contained in:
parent
6d70002233
commit
21d35f88d8
2 changed files with 45 additions and 34 deletions
|
@ -186,8 +186,8 @@ transfer_list = stat "transfers in progress" $ nojson $ lift $ do
|
||||||
[ show (transferDirection t) ++ "ing"
|
[ show (transferDirection t) ++ "ing"
|
||||||
, fromMaybe (show $ transferKey t) (associatedFile i)
|
, fromMaybe (show $ transferKey t) (associatedFile i)
|
||||||
, if transferDirection t == Upload then "to" else "from"
|
, if transferDirection t == Upload then "to" else "from"
|
||||||
, maybe (fromUUID $ transferRemote t) Remote.name $
|
, maybe (fromUUID $ transferUUID t) Remote.name $
|
||||||
M.lookup (transferRemote t) uuidmap
|
M.lookup (transferUUID t) uuidmap
|
||||||
]
|
]
|
||||||
|
|
||||||
disk_size :: Stat
|
disk_size :: Stat
|
||||||
|
|
|
@ -1,4 +1,4 @@
|
||||||
{- git-annex transfer information files
|
{- git-annex transfer information files and lock files
|
||||||
-
|
-
|
||||||
- Copyright 2012 Joey Hess <joey@kitenet.net>
|
- Copyright 2012 Joey Hess <joey@kitenet.net>
|
||||||
-
|
-
|
||||||
|
@ -14,15 +14,18 @@ import qualified Git
|
||||||
import Types.Remote
|
import Types.Remote
|
||||||
import qualified Fields
|
import qualified Fields
|
||||||
|
|
||||||
import Control.Concurrent
|
|
||||||
import System.Posix.Types
|
import System.Posix.Types
|
||||||
import Data.Time.Clock
|
import Data.Time.Clock
|
||||||
|
import Data.Time.Clock.POSIX
|
||||||
|
import Data.Time
|
||||||
|
import System.Locale
|
||||||
|
import Control.Concurrent
|
||||||
|
|
||||||
{- Enough information to uniquely identify a transfer, used as the filename
|
{- Enough information to uniquely identify a transfer, used as the filename
|
||||||
- of the transfer information file. -}
|
- of the transfer information file. -}
|
||||||
data Transfer = Transfer
|
data Transfer = Transfer
|
||||||
{ transferDirection :: Direction
|
{ transferDirection :: Direction
|
||||||
, transferRemote :: UUID
|
, transferUUID :: UUID
|
||||||
, transferKey :: Key
|
, transferKey :: Key
|
||||||
}
|
}
|
||||||
deriving (Show, Eq, Ord)
|
deriving (Show, Eq, Ord)
|
||||||
|
@ -34,9 +37,10 @@ data Transfer = Transfer
|
||||||
- of some repository, that was acted on to initiate the transfer.
|
- of some repository, that was acted on to initiate the transfer.
|
||||||
-}
|
-}
|
||||||
data TransferInfo = TransferInfo
|
data TransferInfo = TransferInfo
|
||||||
{ startedTime :: Maybe UTCTime
|
{ startedTime :: Maybe POSIXTime
|
||||||
, transferPid :: Maybe ProcessID
|
, transferPid :: Maybe ProcessID
|
||||||
, transferThread :: Maybe ThreadId
|
, transferTid :: Maybe ThreadId
|
||||||
|
, transferRemote :: Maybe Remote
|
||||||
, bytesComplete :: Maybe Integer
|
, bytesComplete :: Maybe Integer
|
||||||
, associatedFile :: Maybe FilePath
|
, associatedFile :: Maybe FilePath
|
||||||
}
|
}
|
||||||
|
@ -66,9 +70,9 @@ fieldTransfer direction key a = do
|
||||||
maybe a (\u -> transfer (Transfer direction (toUUID u) key) afile a)
|
maybe a (\u -> transfer (Transfer direction (toUUID u) key) afile a)
|
||||||
=<< Fields.getField Fields.remoteUUID
|
=<< Fields.getField Fields.remoteUUID
|
||||||
|
|
||||||
{- Runs a transfer action. Creates and locks the transfer information file
|
{- Runs a transfer action. Creates and locks the lock file while the
|
||||||
- while the action is running. Will throw an error if the transfer is
|
- action is running, and stores info in the transfer information
|
||||||
- already in progress.
|
- file. Will throw an error if the transfer is already in progress.
|
||||||
-}
|
-}
|
||||||
transfer :: Transfer -> Maybe FilePath -> Annex a -> Annex a
|
transfer :: Transfer -> Maybe FilePath -> Annex a -> Annex a
|
||||||
transfer t file a = do
|
transfer t file a = do
|
||||||
|
@ -76,27 +80,27 @@ transfer t file a = do
|
||||||
createAnnexDirectory $ takeDirectory tfile
|
createAnnexDirectory $ takeDirectory tfile
|
||||||
mode <- annexFileMode
|
mode <- annexFileMode
|
||||||
info <- liftIO $ TransferInfo
|
info <- liftIO $ TransferInfo
|
||||||
<$> (Just <$> getCurrentTime)
|
<$> (Just . utcTimeToPOSIXSeconds <$> getCurrentTime)
|
||||||
<*> pure Nothing -- pid not stored in file, so omitted for speed
|
<*> pure Nothing -- pid not stored in file, so omitted for speed
|
||||||
<*> pure Nothing -- threadid not stored in file, so omitted for speed
|
<*> pure Nothing -- tid ditto
|
||||||
<*> pure Nothing -- not 0; transfer may be resuming
|
<*> pure Nothing -- not 0; transfer may be resuming
|
||||||
|
<*> pure Nothing
|
||||||
<*> pure file
|
<*> pure file
|
||||||
bracketIO (prep tfile mode info) (cleanup tfile) a
|
bracketIO (prep tfile mode info) (cleanup tfile) a
|
||||||
where
|
where
|
||||||
prep tfile mode info = do
|
prep tfile mode info = do
|
||||||
fd <- openFd tfile ReadWrite (Just mode)
|
fd <- openFd (transferLockFile tfile) ReadWrite (Just mode)
|
||||||
defaultFileFlags { trunc = True }
|
defaultFileFlags { trunc = True }
|
||||||
locked <- catchMaybeIO $
|
locked <- catchMaybeIO $
|
||||||
setLock fd (WriteLock, AbsoluteSeek, 0, 0)
|
setLock fd (WriteLock, AbsoluteSeek, 0, 0)
|
||||||
when (locked == Nothing) $
|
when (locked == Nothing) $
|
||||||
error $ "transfer already in progress"
|
error $ "transfer already in progress"
|
||||||
h <- fdToHandle fd
|
writeFile tfile $ writeTransferInfo info
|
||||||
hPutStr h $ writeTransferInfo info
|
return fd
|
||||||
hFlush h
|
cleanup tfile fd = do
|
||||||
return h
|
|
||||||
cleanup tfile h = do
|
|
||||||
removeFile tfile
|
removeFile tfile
|
||||||
hClose h
|
removeFile $ transferLockFile tfile
|
||||||
|
closeFd fd
|
||||||
|
|
||||||
{- If a transfer is still running, returns its TransferInfo. -}
|
{- If a transfer is still running, returns its TransferInfo. -}
|
||||||
checkTransfer :: Transfer -> Annex (Maybe TransferInfo)
|
checkTransfer :: Transfer -> Annex (Maybe TransferInfo)
|
||||||
|
@ -104,22 +108,19 @@ checkTransfer t = do
|
||||||
mode <- annexFileMode
|
mode <- annexFileMode
|
||||||
tfile <- fromRepo $ transferFile t
|
tfile <- fromRepo $ transferFile t
|
||||||
mfd <- liftIO $ catchMaybeIO $
|
mfd <- liftIO $ catchMaybeIO $
|
||||||
openFd tfile ReadOnly (Just mode) defaultFileFlags
|
openFd (transferLockFile tfile) ReadOnly (Just mode) defaultFileFlags
|
||||||
case mfd of
|
case mfd of
|
||||||
Nothing -> return Nothing -- failed to open file; not running
|
Nothing -> return Nothing -- failed to open file; not running
|
||||||
Just fd -> do
|
Just fd -> do
|
||||||
locked <- liftIO $
|
locked <- liftIO $
|
||||||
getLock fd (WriteLock, AbsoluteSeek, 0, 0)
|
getLock fd (WriteLock, AbsoluteSeek, 0, 0)
|
||||||
|
liftIO $ closeFd fd
|
||||||
case locked of
|
case locked of
|
||||||
Nothing -> do
|
Nothing -> return Nothing
|
||||||
liftIO $ closeFd fd
|
Just (pid, _) -> liftIO $
|
||||||
return Nothing
|
flip catchDefaultIO Nothing $ do
|
||||||
Just (pid, _) -> liftIO $ do
|
readTransferInfo pid
|
||||||
h <- fdToHandle fd
|
<$> readFile tfile
|
||||||
info <- readTransferInfo pid
|
|
||||||
<$> hGetContentsStrict h
|
|
||||||
hClose h
|
|
||||||
return info
|
|
||||||
|
|
||||||
{- Gets all currently running transfers. -}
|
{- Gets all currently running transfers. -}
|
||||||
getTransfers :: Annex [(Transfer, TransferInfo)]
|
getTransfers :: Annex [(Transfer, TransferInfo)]
|
||||||
|
@ -140,10 +141,16 @@ transferFile (Transfer direction u key) r = gitAnnexTransferDir r
|
||||||
</> fromUUID u
|
</> fromUUID u
|
||||||
</> keyFile key
|
</> keyFile key
|
||||||
|
|
||||||
|
{- The transfer lock file corresponding to a given transfer info file. -}
|
||||||
|
transferLockFile :: FilePath -> FilePath
|
||||||
|
transferLockFile infofile = let (d,f) = splitFileName infofile in
|
||||||
|
combine d ("lck." ++ f)
|
||||||
|
|
||||||
{- Parses a transfer information filename to a Transfer. -}
|
{- Parses a transfer information filename to a Transfer. -}
|
||||||
parseTransferFile :: FilePath -> Maybe Transfer
|
parseTransferFile :: FilePath -> Maybe Transfer
|
||||||
parseTransferFile file =
|
parseTransferFile file
|
||||||
case drop (length bits - 3) bits of
|
| "lck." `isPrefixOf` (takeFileName file) = Nothing
|
||||||
|
| otherwise = case drop (length bits - 3) bits of
|
||||||
[direction, u, key] -> Transfer
|
[direction, u, key] -> Transfer
|
||||||
<$> readDirection direction
|
<$> readDirection direction
|
||||||
<*> pure (toUUID u)
|
<*> pure (toUUID u)
|
||||||
|
@ -156,8 +163,7 @@ writeTransferInfo :: TransferInfo -> String
|
||||||
writeTransferInfo info = unlines
|
writeTransferInfo info = unlines
|
||||||
-- transferPid is not included; instead obtained by looking at
|
-- transferPid is not included; instead obtained by looking at
|
||||||
-- the process that locks the file.
|
-- the process that locks the file.
|
||||||
-- transferThread is not included; not relevant for other processes
|
[ maybe "" show $ startedTime info
|
||||||
[ show $ startedTime info
|
|
||||||
-- bytesComplete is not included; changes too fast
|
-- bytesComplete is not included; changes too fast
|
||||||
, fromMaybe "" $ associatedFile info -- comes last; arbitrary content
|
, fromMaybe "" $ associatedFile info -- comes last; arbitrary content
|
||||||
]
|
]
|
||||||
|
@ -166,12 +172,17 @@ readTransferInfo :: ProcessID -> String -> Maybe TransferInfo
|
||||||
readTransferInfo pid s =
|
readTransferInfo pid s =
|
||||||
case bits of
|
case bits of
|
||||||
[time] -> TransferInfo
|
[time] -> TransferInfo
|
||||||
<$> readish time
|
<$> (Just <$> parsePOSIXTime time)
|
||||||
<*> pure (Just pid)
|
<*> pure (Just pid)
|
||||||
<*> pure Nothing
|
<*> pure Nothing
|
||||||
<*> pure Nothing
|
<*> pure Nothing
|
||||||
|
<*> pure Nothing
|
||||||
<*> pure (if null filename then Nothing else Just filename)
|
<*> pure (if null filename then Nothing else Just filename)
|
||||||
_ -> Nothing
|
_ -> Nothing
|
||||||
where
|
where
|
||||||
(bits, filebits) = splitAt 1 $ lines s
|
(bits, filebits) = splitAt 1 $ lines s
|
||||||
filename = join "\n" filebits
|
filename = join "\n" filebits
|
||||||
|
|
||||||
|
parsePOSIXTime :: String -> Maybe POSIXTime
|
||||||
|
parsePOSIXTime s = utcTimeToPOSIXSeconds
|
||||||
|
<$> parseTime defaultTimeLocale "%s%Qs" s
|
||||||
|
|
Loading…
Add table
Reference in a new issue