4ac2fd0a22
I now have this topology working: assistant ---> {bare repo, special remote} <--- assistant And, I think, also this one: +----------- bare repo --------+ v v assistant ---> special remote <--- assistant While before with assistant <---> assistant connections, both sides got location info updated after a transfer, in this topology, the bare repo *might* get its location info updated, but the other assistant has no way to know that it did. And a special remote doesn't record location info, so transfers to it won't propigate out location log changes at all. So, for these to work, after a transfer succeeds, the git-annex branch needs to be pushed. This is done by recording a synthetic commit has occurred, which lets the pusher handle pushing out the change (which will include actually committing any still journalled changes to the git-annex branch). Of course, this means rather a lot more syncing action than happened before. At least the pusher bundles together very close together pushes, somewhat. Currently it just waits 2 seconds between each push.
83 lines
2.6 KiB
Haskell
83 lines
2.6 KiB
Haskell
{- git-annex assistant git pushing thread
|
|
-
|
|
- Copyright 2012 Joey Hess <joey@kitenet.net>
|
|
-
|
|
- Licensed under the GNU GPL version 3 or higher.
|
|
-}
|
|
|
|
module Assistant.Threads.Pusher where
|
|
|
|
import Assistant.Common
|
|
import Assistant.Commits
|
|
import Assistant.Pushes
|
|
import Assistant.Alert
|
|
import Assistant.ThreadedMonad
|
|
import Assistant.DaemonStatus
|
|
import Assistant.Sync
|
|
import Utility.ThreadScheduler
|
|
import qualified Remote
|
|
import qualified Types.Remote as Remote
|
|
|
|
import Data.Time.Clock
|
|
|
|
thisThread :: ThreadName
|
|
thisThread = "Pusher"
|
|
|
|
{- This thread retries pushes that failed before. -}
|
|
pushRetryThread :: ThreadState -> DaemonStatusHandle -> FailedPushMap -> PushNotifier -> NamedThread
|
|
pushRetryThread st dstatus pushmap pushnotifier = thread $ runEvery (Seconds halfhour) $ do
|
|
-- We already waited half an hour, now wait until there are failed
|
|
-- pushes to retry.
|
|
topush <- getFailedPushesBefore pushmap (fromIntegral halfhour)
|
|
unless (null topush) $ do
|
|
debug thisThread
|
|
[ "retrying"
|
|
, show (length topush)
|
|
, "failed pushes"
|
|
]
|
|
now <- getCurrentTime
|
|
void $ alertWhile dstatus (pushRetryAlert topush) $
|
|
pushToRemotes thisThread now st (Just pushnotifier) (Just pushmap) topush
|
|
where
|
|
halfhour = 1800
|
|
thread = NamedThread thisThread
|
|
|
|
{- This thread pushes git commits out to remotes soon after they are made. -}
|
|
pushThread :: ThreadState -> DaemonStatusHandle -> CommitChan -> FailedPushMap -> PushNotifier -> NamedThread
|
|
pushThread st dstatus commitchan pushmap pushnotifier = thread $ runEvery (Seconds 2) $ do
|
|
-- We already waited two seconds as a simple rate limiter.
|
|
-- Next, wait until at least one commit has been made
|
|
commits <- getCommits commitchan
|
|
-- Now see if now's a good time to push.
|
|
if shouldPush commits
|
|
then do
|
|
remotes <- filter pushable . syncRemotes
|
|
<$> getDaemonStatus dstatus
|
|
unless (null remotes) $ do
|
|
now <- getCurrentTime
|
|
void $ alertWhile dstatus (pushAlert remotes) $
|
|
pushToRemotes thisThread now st (Just pushnotifier) (Just pushmap) remotes
|
|
else do
|
|
debug thisThread
|
|
[ "delaying push of"
|
|
, show (length commits)
|
|
, "commits"
|
|
]
|
|
refillCommits commitchan commits
|
|
where
|
|
thread = NamedThread thisThread
|
|
pushable r
|
|
| Remote.specialRemote r = False
|
|
| Remote.readonly r = False
|
|
| otherwise = True
|
|
|
|
{- Decide if now is a good time to push to remotes.
|
|
-
|
|
- Current strategy: Immediately push all commits. The commit machinery
|
|
- already determines batches of changes, so we can't easily determine
|
|
- batches better.
|
|
-}
|
|
shouldPush :: [Commit] -> Bool
|
|
shouldPush commits
|
|
| not (null commits) = True
|
|
| otherwise = False
|