data:image/s3,"s3://crabby-images/62dab/62dab3f2178ca2f67cfd1d6319f72c44dec3744c" alt="Joey Hess"
Hooked up everything that needs to notify on pushes. Note that syncNewRemote does not notify. This is probably ok, and I'd need to thread more state through to make it do so. This is only set up to support a single push notification method; I didn't use a NotificationBroadcaster. Partly because I don't yet know what info about pushes needs to be communicated, so my data types are only preliminary.
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.
|
|
now <- getCurrentTime
|
|
if shouldPush now commits
|
|
then do
|
|
remotes <- filter pushable . syncRemotes
|
|
<$> getDaemonStatus dstatus
|
|
unless (null remotes) $
|
|
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 :: UTCTime -> [Commit] -> Bool
|
|
shouldPush _now commits
|
|
| not (null commits) = True
|
|
| otherwise = False
|