add additional debug info about reasons for transfers
This commit is contained in:
parent
e2f1f7afc6
commit
46c9cbeb1e
9 changed files with 43 additions and 31 deletions
|
@ -216,7 +216,7 @@ handleAdds delayadd cs = returnWhen (null incomplete) $ do
|
||||||
whenM (pure DirWatcher.eventsCoalesce <||> isDirect) $ do
|
whenM (pure DirWatcher.eventsCoalesce <||> isDirect) $ do
|
||||||
stageSymlink file =<< hashSymlink link
|
stageSymlink file =<< hashSymlink link
|
||||||
showEndOk
|
showEndOk
|
||||||
queueTransfers Next key (Just file) Upload
|
queueTransfers "newly added file" Next key (Just file) Upload
|
||||||
return $ Just change
|
return $ Just change
|
||||||
|
|
||||||
{- Check that the keysource's keyFilename still exists,
|
{- Check that the keysource's keyFilename still exists,
|
||||||
|
|
|
@ -39,5 +39,5 @@ glacierThread = namedThread "Glacier" $ runEvery (Seconds 3600) <~> go
|
||||||
let l' = filter (\p -> S.member (getkey p) s) l
|
let l' = filter (\p -> S.member (getkey p) s) l
|
||||||
forM_ l' $ \(t, info) -> do
|
forM_ l' $ \(t, info) -> do
|
||||||
liftAnnex $ removeFailedTransfer t
|
liftAnnex $ removeFailedTransfer t
|
||||||
queueTransferWhenSmall (associatedFile info) t r
|
queueTransferWhenSmall "object available from glacier" (associatedFile info) t r
|
||||||
getkey = transferKey . fst
|
getkey = transferKey . fst
|
||||||
|
|
|
@ -65,7 +65,7 @@ onAdd file
|
||||||
| isAnnexBranch file = do
|
| isAnnexBranch file = do
|
||||||
branchChanged
|
branchChanged
|
||||||
whenM (liftAnnex Annex.Branch.forceUpdate) $
|
whenM (liftAnnex Annex.Branch.forceUpdate) $
|
||||||
queueDeferredDownloads Later
|
queueDeferredDownloads "retrying deferred download" Later
|
||||||
| "/synced/" `isInfixOf` file = do
|
| "/synced/" `isInfixOf` file = do
|
||||||
mergecurrent =<< liftAnnex (inRepo Git.Branch.current)
|
mergecurrent =<< liftAnnex (inRepo Git.Branch.current)
|
||||||
| otherwise = noop
|
| otherwise = noop
|
||||||
|
|
|
@ -78,7 +78,7 @@ failedTransferScan r = do
|
||||||
- that the remote doesn't already have the
|
- that the remote doesn't already have the
|
||||||
- key, so it's not redundantly checked here. -}
|
- key, so it's not redundantly checked here. -}
|
||||||
requeue t info
|
requeue t info
|
||||||
requeue t info = queueTransferWhenSmall (associatedFile info) t r
|
requeue t info = queueTransferWhenSmall "retrying failed transfer" (associatedFile info) t r
|
||||||
|
|
||||||
{- This is a expensive scan through the full git work tree, finding
|
{- This is a expensive scan through the full git work tree, finding
|
||||||
- files to transfer. The scan is blocked when the transfer queue gets
|
- files to transfer. The scan is blocked when the transfer queue gets
|
||||||
|
@ -108,9 +108,9 @@ expensiveScan rs = unless onlyweb $ do
|
||||||
onlyweb = all (== webUUID) $ map Remote.uuid rs
|
onlyweb = all (== webUUID) $ map Remote.uuid rs
|
||||||
visiblers = let rs' = filter (not . Remote.readonly) rs
|
visiblers = let rs' = filter (not . Remote.readonly) rs
|
||||||
in if null rs' then rs else rs'
|
in if null rs' then rs else rs'
|
||||||
enqueue f (r, t) = do
|
enqueue f (r, t) =
|
||||||
debug ["queuing", show t]
|
queueTransferWhenSmall "expensive scan found missing object"
|
||||||
queueTransferWhenSmall (Just f) t r
|
(Just f) t r
|
||||||
findtransfers f (key, _) = do
|
findtransfers f (key, _) = do
|
||||||
{- The syncable remotes may have changed since this
|
{- The syncable remotes may have changed since this
|
||||||
- scan began. -}
|
- scan began. -}
|
||||||
|
|
|
@ -61,7 +61,7 @@ onAdd file = case parseTransferFile file of
|
||||||
where
|
where
|
||||||
go _ Nothing = noop -- transfer already finished
|
go _ Nothing = noop -- transfer already finished
|
||||||
go t (Just info) = do
|
go t (Just info) = do
|
||||||
debug [ "transfer starting:", show t]
|
debug [ "transfer starting:", describeTransfer t info ]
|
||||||
r <- headMaybe . filter (sameuuid t)
|
r <- headMaybe . filter (sameuuid t)
|
||||||
<$> liftAnnex Remote.remoteList
|
<$> liftAnnex Remote.remoteList
|
||||||
updateTransferInfo t info { transferRemote = r }
|
updateTransferInfo t info { transferRemote = r }
|
||||||
|
@ -116,8 +116,9 @@ finishedTransfer t (Just info)
|
||||||
| transferDirection t == Download =
|
| transferDirection t == Download =
|
||||||
whenM (liftAnnex $ inAnnex $ transferKey t) $ do
|
whenM (liftAnnex $ inAnnex $ transferKey t) $ do
|
||||||
handleDrops False (transferKey t) (associatedFile info) Nothing
|
handleDrops False (transferKey t) (associatedFile info) Nothing
|
||||||
queueTransfersMatching (/= transferUUID t) Later
|
queueTransfersMatching (/= transferUUID t)
|
||||||
(transferKey t) (associatedFile info) Upload
|
"newly received object"
|
||||||
|
Later (transferKey t) (associatedFile info) Upload
|
||||||
| otherwise = handleDrops True (transferKey t) (associatedFile info) Nothing
|
| otherwise = handleDrops True (transferKey t) (associatedFile info) Nothing
|
||||||
finishedTransfer _ _ = noop
|
finishedTransfer _ _ = noop
|
||||||
|
|
||||||
|
|
|
@ -40,11 +40,11 @@ startTransfer :: FilePath -> Transfer -> TransferInfo -> Assistant (Maybe (Trans
|
||||||
startTransfer program t info = case (transferRemote info, associatedFile info) of
|
startTransfer program t info = case (transferRemote info, associatedFile info) of
|
||||||
(Just remote, Just file) -> ifM (liftAnnex $ shouldTransfer t info)
|
(Just remote, Just file) -> ifM (liftAnnex $ shouldTransfer t info)
|
||||||
( do
|
( do
|
||||||
debug [ "Transferring:" , show t ]
|
debug [ "Transferring:" , describeTransfer t info ]
|
||||||
notifyTransfer
|
notifyTransfer
|
||||||
return $ Just (t, info, transferprocess remote file)
|
return $ Just (t, info, transferprocess remote file)
|
||||||
, do
|
, do
|
||||||
debug [ "Skipping unnecessary transfer:" , show t ]
|
debug [ "Skipping unnecessary transfer:" , describeTransfer t info ]
|
||||||
void $ removeTransfer t
|
void $ removeTransfer t
|
||||||
return Nothing
|
return Nothing
|
||||||
)
|
)
|
||||||
|
|
|
@ -252,8 +252,8 @@ onAddSymlink file filestatus = go =<< liftAnnex (Backend.lookupFile file)
|
||||||
| scanComplete daemonstatus = do
|
| scanComplete daemonstatus = do
|
||||||
present <- liftAnnex $ inAnnex key
|
present <- liftAnnex $ inAnnex key
|
||||||
if present
|
if present
|
||||||
then queueTransfers Next key (Just file) Upload
|
then queueTransfers "new file created" Next key (Just file) Upload
|
||||||
else queueTransfers Next key (Just file) Download
|
else queueTransfers "new or renamed file wanted" Next key (Just file) Download
|
||||||
handleDrops present key (Just file) Nothing
|
handleDrops present key (Just file) Nothing
|
||||||
| otherwise = noop
|
| otherwise = noop
|
||||||
|
|
||||||
|
|
|
@ -33,6 +33,8 @@ import Annex.Wanted
|
||||||
import Control.Concurrent.STM
|
import Control.Concurrent.STM
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
|
|
||||||
|
type Reason = String
|
||||||
|
|
||||||
{- Reads the queue's content without blocking or changing it. -}
|
{- Reads the queue's content without blocking or changing it. -}
|
||||||
getTransferQueue :: Assistant [(Transfer, TransferInfo)]
|
getTransferQueue :: Assistant [(Transfer, TransferInfo)]
|
||||||
getTransferQueue = (atomically . readTVar . queuelist) <<~ transferQueue
|
getTransferQueue = (atomically . readTVar . queuelist) <<~ transferQueue
|
||||||
|
@ -45,13 +47,13 @@ stubInfo f r = stubTransferInfo
|
||||||
|
|
||||||
{- Adds transfers to queue for some of the known remotes.
|
{- Adds transfers to queue for some of the known remotes.
|
||||||
- Honors preferred content settings, only transferring wanted files. -}
|
- Honors preferred content settings, only transferring wanted files. -}
|
||||||
queueTransfers :: Schedule -> Key -> AssociatedFile -> Direction -> Assistant ()
|
queueTransfers :: Reason -> Schedule -> Key -> AssociatedFile -> Direction -> Assistant ()
|
||||||
queueTransfers = queueTransfersMatching (const True)
|
queueTransfers = queueTransfersMatching (const True)
|
||||||
|
|
||||||
{- Adds transfers to queue for some of the known remotes, that match a
|
{- Adds transfers to queue for some of the known remotes, that match a
|
||||||
- condition. Honors preferred content settings. -}
|
- condition. Honors preferred content settings. -}
|
||||||
queueTransfersMatching :: (UUID -> Bool) -> Schedule -> Key -> AssociatedFile -> Direction -> Assistant ()
|
queueTransfersMatching :: (UUID -> Bool) -> Reason -> Schedule -> Key -> AssociatedFile -> Direction -> Assistant ()
|
||||||
queueTransfersMatching matching schedule k f direction
|
queueTransfersMatching matching reason schedule k f direction
|
||||||
| direction == Download = whenM (liftAnnex $ wantGet True f) go
|
| direction == Download = whenM (liftAnnex $ wantGet True f) go
|
||||||
| otherwise = go
|
| otherwise = go
|
||||||
where
|
where
|
||||||
|
@ -62,7 +64,7 @@ queueTransfersMatching matching schedule k f direction
|
||||||
if null matchingrs
|
if null matchingrs
|
||||||
then defer
|
then defer
|
||||||
else forM_ matchingrs $ \r ->
|
else forM_ matchingrs $ \r ->
|
||||||
enqueue schedule (gentransfer r) (stubInfo f r)
|
enqueue reason schedule (gentransfer r) (stubInfo f r)
|
||||||
sufficientremotes rs
|
sufficientremotes rs
|
||||||
{- Queue downloads from all remotes that
|
{- Queue downloads from all remotes that
|
||||||
- have the key, with the cheapest ones first.
|
- have the key, with the cheapest ones first.
|
||||||
|
@ -90,8 +92,8 @@ queueTransfersMatching matching schedule k f direction
|
||||||
|
|
||||||
{- Queues any deferred downloads that can now be accomplished, leaving
|
{- Queues any deferred downloads that can now be accomplished, leaving
|
||||||
- any others in the list to try again later. -}
|
- any others in the list to try again later. -}
|
||||||
queueDeferredDownloads :: Schedule -> Assistant ()
|
queueDeferredDownloads :: Reason -> Schedule -> Assistant ()
|
||||||
queueDeferredDownloads schedule = do
|
queueDeferredDownloads reason schedule = do
|
||||||
q <- getAssistant transferQueue
|
q <- getAssistant transferQueue
|
||||||
l <- liftIO $ atomically $ swapTVar (deferreddownloads q) []
|
l <- liftIO $ atomically $ swapTVar (deferreddownloads q) []
|
||||||
rs <- syncDataRemotes <$> getDaemonStatus
|
rs <- syncDataRemotes <$> getDaemonStatus
|
||||||
|
@ -105,7 +107,7 @@ queueDeferredDownloads schedule = do
|
||||||
let sources = filter (\r -> uuid r `elem` uuids) rs
|
let sources = filter (\r -> uuid r `elem` uuids) rs
|
||||||
unless (null sources) $
|
unless (null sources) $
|
||||||
forM_ sources $ \r ->
|
forM_ sources $ \r ->
|
||||||
enqueue schedule (gentransfer r) (stubInfo f r)
|
enqueue reason schedule (gentransfer r) (stubInfo f r)
|
||||||
return $ null sources
|
return $ null sources
|
||||||
where
|
where
|
||||||
gentransfer r = Transfer
|
gentransfer r = Transfer
|
||||||
|
@ -114,8 +116,8 @@ queueDeferredDownloads schedule = do
|
||||||
, transferUUID = Remote.uuid r
|
, transferUUID = Remote.uuid r
|
||||||
}
|
}
|
||||||
|
|
||||||
enqueue :: Schedule -> Transfer -> TransferInfo -> Assistant ()
|
enqueue :: Reason -> Schedule -> Transfer -> TransferInfo -> Assistant ()
|
||||||
enqueue schedule t info
|
enqueue reason schedule t info
|
||||||
| schedule == Next = go (new:)
|
| schedule == Next = go (new:)
|
||||||
| otherwise = go (\l -> l++[new])
|
| otherwise = go (\l -> l++[new])
|
||||||
where
|
where
|
||||||
|
@ -125,31 +127,33 @@ enqueue schedule t info
|
||||||
liftIO $ atomically $ do
|
liftIO $ atomically $ do
|
||||||
void $ modifyTVar' (queuesize q) succ
|
void $ modifyTVar' (queuesize q) succ
|
||||||
void $ modifyTVar' (queuelist q) modlist
|
void $ modifyTVar' (queuelist q) modlist
|
||||||
|
debug [ "queued", describeTransfer t info, ": " ++ reason ]
|
||||||
notifyTransfer
|
notifyTransfer
|
||||||
|
|
||||||
{- Adds a transfer to the queue. -}
|
{- Adds a transfer to the queue. -}
|
||||||
queueTransfer :: Schedule -> AssociatedFile -> Transfer -> Remote -> Assistant ()
|
queueTransfer :: Reason -> Schedule -> AssociatedFile -> Transfer -> Remote -> Assistant ()
|
||||||
queueTransfer schedule f t remote = enqueue schedule t (stubInfo f remote)
|
queueTransfer reason schedule f t remote =
|
||||||
|
enqueue reason schedule t (stubInfo f remote)
|
||||||
|
|
||||||
{- Blocks until the queue is no larger than a given size, and then adds a
|
{- Blocks until the queue is no larger than a given size, and then adds a
|
||||||
- transfer to the queue. -}
|
- transfer to the queue. -}
|
||||||
queueTransferAt :: Int -> Schedule -> AssociatedFile -> Transfer -> Remote -> Assistant ()
|
queueTransferAt :: Int -> Reason -> Schedule -> AssociatedFile -> Transfer -> Remote -> Assistant ()
|
||||||
queueTransferAt wantsz schedule f t remote = do
|
queueTransferAt wantsz reason schedule f t remote = do
|
||||||
q <- getAssistant transferQueue
|
q <- getAssistant transferQueue
|
||||||
liftIO $ atomically $ do
|
liftIO $ atomically $ do
|
||||||
sz <- readTVar (queuesize q)
|
sz <- readTVar (queuesize q)
|
||||||
unless (sz <= wantsz) $
|
unless (sz <= wantsz) $
|
||||||
retry -- blocks until queuesize changes
|
retry -- blocks until queuesize changes
|
||||||
enqueue schedule t (stubInfo f remote)
|
enqueue reason schedule t (stubInfo f remote)
|
||||||
|
|
||||||
queueTransferWhenSmall :: AssociatedFile -> Transfer -> Remote -> Assistant ()
|
queueTransferWhenSmall :: Reason -> AssociatedFile -> Transfer -> Remote -> Assistant ()
|
||||||
queueTransferWhenSmall = queueTransferAt 10 Later
|
queueTransferWhenSmall reason = queueTransferAt 10 reason Later
|
||||||
|
|
||||||
{- Blocks until a pending transfer is available in the queue,
|
{- Blocks until a pending transfer is available in the queue,
|
||||||
- and removes it.
|
- and removes it.
|
||||||
-
|
-
|
||||||
- Checks that it's acceptable, before adding it to the
|
- Checks that it's acceptable, before adding it to the
|
||||||
- the currentTransfers map. If it's not acceptable, it's discarded.
|
- currentTransfers map. If it's not acceptable, it's discarded.
|
||||||
-
|
-
|
||||||
- This is done in a single STM transaction, so there is no window
|
- This is done in a single STM transaction, so there is no window
|
||||||
- where an observer sees an inconsistent status. -}
|
- where an observer sees an inconsistent status. -}
|
||||||
|
|
|
@ -64,6 +64,13 @@ readLcDirection "upload" = Just Upload
|
||||||
readLcDirection "download" = Just Download
|
readLcDirection "download" = Just Download
|
||||||
readLcDirection _ = Nothing
|
readLcDirection _ = Nothing
|
||||||
|
|
||||||
|
describeTransfer :: Transfer -> TransferInfo -> String
|
||||||
|
describeTransfer t info = unwords
|
||||||
|
[ show $ transferDirection t
|
||||||
|
, show $ transferUUID t
|
||||||
|
, fromMaybe (key2file $ transferKey t) (associatedFile info)
|
||||||
|
]
|
||||||
|
|
||||||
{- Transfers that will accomplish the same task. -}
|
{- Transfers that will accomplish the same task. -}
|
||||||
equivilantTransfer :: Transfer -> Transfer -> Bool
|
equivilantTransfer :: Transfer -> Transfer -> Bool
|
||||||
equivilantTransfer t1 t2
|
equivilantTransfer t1 t2
|
||||||
|
|
Loading…
Reference in a new issue