git-annex/Assistant/Pushes.hs
Joey Hess 32497feb2a initial implementation of XMPP push notifier (untested)
Lacking error handling, reconnection, credentials configuration,
and doesn't actually do anything when it receives an incoming notification.

Other than that, it might work! :)
2012-10-24 15:42:02 -04:00

59 lines
1.8 KiB
Haskell

{- git-annex assistant push tracking
-
- Copyright 2012 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU GPL version 3 or higher.
-}
module Assistant.Pushes where
import Common.Annex
import Utility.TSet
import Control.Concurrent.STM
import Data.Time.Clock
import qualified Data.Map as M
{- Track the most recent push failure for each remote. -}
type PushMap = M.Map Remote UTCTime
type FailedPushMap = TMVar PushMap
{- Used to notify about successful pushes. -}
newtype PushNotifier = PushNotifier (TSet UUID)
{- The TMVar starts empty, and is left empty when there are no
- failed pushes. This way we can block until there are some failed pushes.
-}
newFailedPushMap :: IO FailedPushMap
newFailedPushMap = atomically newEmptyTMVar
{- Blocks until there are failed pushes.
- Returns Remotes whose pushes failed a given time duration or more ago.
- (This may be an empty list.) -}
getFailedPushesBefore :: FailedPushMap -> NominalDiffTime -> IO [Remote]
getFailedPushesBefore v duration = do
m <- atomically $ readTMVar v
now <- getCurrentTime
return $ M.keys $ M.filter (not . toorecent now) m
where
toorecent now time = now `diffUTCTime` time < duration
{- Modifies the map. -}
changeFailedPushMap :: FailedPushMap -> (PushMap -> PushMap) -> IO ()
changeFailedPushMap v a = atomically $
store . a . fromMaybe M.empty =<< tryTakeTMVar v
where
{- tryTakeTMVar empties the TMVar; refill it only if
- the modified map is not itself empty -}
store m
| m == M.empty = noop
| otherwise = putTMVar v $! m
newPushNotifier :: IO PushNotifier
newPushNotifier = PushNotifier <$> newTSet
notifyPush :: [UUID] -> PushNotifier -> IO ()
notifyPush us (PushNotifier s) = putTSet s us
waitPush :: PushNotifier -> IO [UUID]
waitPush (PushNotifier s) = getTSet s