diff options
author | Joey Hess <joey@kitenet.net> | 2012-08-22 14:32:17 -0400 |
---|---|---|
committer | Joey Hess <joey@kitenet.net> | 2012-08-22 14:32:17 -0400 |
commit | 68659f49983ca30a3c1a1a3f5e7da003f96741dc (patch) | |
tree | 31e100dcd657840b9628b043681bdd4a7e48e1c1 /Assistant/Sync.hs | |
parent | 5a68acb521bae0277b2c8a8ca023dc57a5ff4b33 (diff) |
refactor
Diffstat (limited to 'Assistant/Sync.hs')
-rw-r--r-- | Assistant/Sync.hs | 98 |
1 files changed, 98 insertions, 0 deletions
diff --git a/Assistant/Sync.hs b/Assistant/Sync.hs new file mode 100644 index 000000000..68053167a --- /dev/null +++ b/Assistant/Sync.hs @@ -0,0 +1,98 @@ +{- git-annex assistant repo syncing + - + - Copyright 2012 Joey Hess <joey@kitenet.net> + - + - Licensed under the GNU GPL version 3 or higher. + -} + +module Assistant.Sync where + +import Assistant.Common +import Assistant.Pushes +import Assistant.Alert +import Assistant.ThreadedMonad +import Assistant.DaemonStatus +import Assistant.ScanRemotes +import qualified Command.Sync +import Utility.Parallel +import qualified Git +import qualified Git.Branch +import qualified Git.Command +import qualified Remote +import qualified Annex.Branch + +import Data.Time.Clock +import qualified Data.Map as M + +{- Syncs with remotes that may have been disconnected for a while. + - + - After getting git in sync, queues a scan for file transfers. + -} +syncRemotes :: ThreadName -> ThreadState -> DaemonStatusHandle -> ScanRemoteMap -> [Remote] -> IO () +syncRemotes _ _ _ _ [] = noop +syncRemotes threadname st dstatus scanremotes rs = do + void $ alertWhile dstatus (syncAlert rs) $ do + sync =<< runThreadState st (inRepo Git.Branch.current) + addScanRemotes scanremotes rs + where + sync (Just branch) = do + runThreadState st $ manualPull (Just branch) rs + now <- getCurrentTime + pushToRemotes threadname now st Nothing rs + {- No local branch exists yet, but we can try pulling. -} + sync Nothing = do + runThreadState st $ manualPull Nothing rs + return True + +{- Updates the local sync branch, then pushes it to all remotes, in + - parallel. + - + - Avoids running possibly long-duration commands in the Annex monad, so + - as not to block other threads. -} +pushToRemotes :: ThreadName -> UTCTime -> ThreadState -> (Maybe FailedPushMap) -> [Remote] -> IO Bool +pushToRemotes threadname now st mpushmap remotes = do + (g, branch) <- runThreadState st $ + (,) <$> fromRepo id <*> inRepo Git.Branch.current + go True branch g remotes + where + go _ Nothing _ _ = return True -- no branch, so nothing to do + go shouldretry (Just branch) g rs = do + debug threadname + [ "pushing to" + , show rs + ] + Command.Sync.updateBranch (Command.Sync.syncBranch branch) g + (succeeded, failed) <- inParallel (push g branch) rs + let ok = null failed + case mpushmap of + Nothing -> noop + Just pushmap -> + changeFailedPushMap pushmap $ \m -> + M.union (makemap failed) $ + M.difference m (makemap succeeded) + unless (ok) $ + debug threadname + [ "failed to push to" + , show failed + ] + if (ok || not shouldretry) + then return ok + else retry branch g failed + + makemap l = M.fromList $ zip l (repeat now) + + push g branch remote = Command.Sync.pushBranch remote branch g + + retry branch g rs = do + debug threadname [ "trying manual pull to resolve failed pushes" ] + runThreadState st $ manualPull (Just branch) rs + go False (Just branch) g rs + +{- Manually pull from remotes and merge their branches. -} +manualPull :: (Maybe Git.Ref) -> [Remote] -> Annex () +manualPull currentbranch remotes = do + forM_ remotes $ \r -> + inRepo $ Git.Command.runBool "fetch" [Param $ Remote.name r] + Annex.Branch.forceUpdate + forM_ remotes $ \r -> + Command.Sync.mergeRemote r currentbranch |