2012-07-23 03:16:56 +00:00
|
|
|
{- git-annex assistant git pushing thread
|
2012-06-22 17:39:44 +00:00
|
|
|
-
|
|
|
|
- Copyright 2012 Joey Hess <joey@kitenet.net>
|
2012-06-23 05:20:40 +00:00
|
|
|
-
|
|
|
|
- Licensed under the GNU GPL version 3 or higher.
|
2012-06-22 17:39:44 +00:00
|
|
|
-}
|
|
|
|
|
2012-06-25 20:10:10 +00:00
|
|
|
module Assistant.Threads.Pusher where
|
2012-06-22 17:39:44 +00:00
|
|
|
|
2012-07-20 23:29:59 +00:00
|
|
|
import Assistant.Common
|
2012-06-22 17:39:44 +00:00
|
|
|
import Assistant.Commits
|
2012-06-25 20:38:12 +00:00
|
|
|
import Assistant.Pushes
|
2012-07-29 21:53:18 +00:00
|
|
|
import Assistant.Alert
|
|
|
|
import Assistant.DaemonStatus
|
2012-08-22 18:32:17 +00:00
|
|
|
import Assistant.Sync
|
2012-06-22 17:39:44 +00:00
|
|
|
import Utility.ThreadScheduler
|
2012-08-26 18:56:26 +00:00
|
|
|
import qualified Remote
|
2012-08-26 19:39:02 +00:00
|
|
|
import qualified Types.Remote as Remote
|
2012-06-22 19:46:21 +00:00
|
|
|
|
|
|
|
import Data.Time.Clock
|
|
|
|
|
2012-07-20 23:29:59 +00:00
|
|
|
thisThread :: ThreadName
|
|
|
|
thisThread = "Pusher"
|
|
|
|
|
2012-06-25 20:38:12 +00:00
|
|
|
{- This thread retries pushes that failed before. -}
|
2012-10-29 15:40:22 +00:00
|
|
|
pushRetryThread :: NamedThread
|
|
|
|
pushRetryThread = NamedThread "PushRetrier" $ runEvery (Seconds halfhour) <~> do
|
2012-06-25 20:38:12 +00:00
|
|
|
-- We already waited half an hour, now wait until there are failed
|
|
|
|
-- pushes to retry.
|
2012-10-29 21:52:43 +00:00
|
|
|
topush <- getFailedPushesBefore (fromIntegral halfhour)
|
2012-06-26 21:33:34 +00:00
|
|
|
unless (null topush) $ do
|
2012-10-29 15:40:22 +00:00
|
|
|
debug ["retrying", show (length topush), "failed pushes"]
|
2012-10-29 20:49:47 +00:00
|
|
|
void $ alertWhile (pushRetryAlert topush) $ do
|
|
|
|
now <- liftIO $ getCurrentTime
|
2012-10-29 20:22:14 +00:00
|
|
|
pushToRemotes now True topush
|
2012-06-25 20:38:12 +00:00
|
|
|
where
|
|
|
|
halfhour = 1800
|
2012-06-22 17:39:44 +00:00
|
|
|
|
2012-06-25 20:38:12 +00:00
|
|
|
{- This thread pushes git commits out to remotes soon after they are made. -}
|
2012-10-29 15:40:22 +00:00
|
|
|
pushThread :: NamedThread
|
|
|
|
pushThread = NamedThread "Pusher" $ runEvery (Seconds 2) <~> do
|
2012-09-13 04:57:52 +00:00
|
|
|
-- We already waited two seconds as a simple rate limiter.
|
|
|
|
-- Next, wait until at least one commit has been made
|
2012-10-29 15:40:22 +00:00
|
|
|
commits <- getCommits <<~ commitChan
|
2012-09-13 04:57:52 +00:00
|
|
|
-- Now see if now's a good time to push.
|
ensure that git-annex branch is pushed after a successful transfer
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.
2012-10-28 20:05:34 +00:00
|
|
|
if shouldPush commits
|
2012-09-13 04:57:52 +00:00
|
|
|
then do
|
2012-10-29 15:40:22 +00:00
|
|
|
remotes <- filter pushable . syncRemotes <$> daemonStatus
|
2012-10-29 20:49:47 +00:00
|
|
|
unless (null remotes) $
|
|
|
|
void $ alertWhile (pushAlert remotes) $ do
|
|
|
|
now <- liftIO $ getCurrentTime
|
2012-10-29 20:22:14 +00:00
|
|
|
pushToRemotes now True remotes
|
2012-09-13 04:57:52 +00:00
|
|
|
else do
|
2012-10-29 15:40:22 +00:00
|
|
|
debug ["delaying push of", show (length commits), "commits"]
|
|
|
|
flip refillCommits commits <<~ commitChan
|
|
|
|
where
|
|
|
|
pushable r
|
|
|
|
| Remote.specialRemote r = False
|
|
|
|
| Remote.readonly r = False
|
|
|
|
| otherwise = True
|
2012-06-22 17:39:44 +00:00
|
|
|
|
2012-06-22 21:01:08 +00:00
|
|
|
{- Decide if now is a good time to push to remotes.
|
2012-06-22 19:46:21 +00:00
|
|
|
-
|
2012-06-22 21:01:08 +00:00
|
|
|
- Current strategy: Immediately push all commits. The commit machinery
|
2012-06-22 19:46:21 +00:00
|
|
|
- already determines batches of changes, so we can't easily determine
|
|
|
|
- batches better.
|
|
|
|
-}
|
ensure that git-annex branch is pushed after a successful transfer
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.
2012-10-28 20:05:34 +00:00
|
|
|
shouldPush :: [Commit] -> Bool
|
|
|
|
shouldPush commits
|
2012-06-22 19:46:21 +00:00
|
|
|
| not (null commits) = True
|
|
|
|
| otherwise = False
|