assistant: Now detects immediately when other repositories push changes to

a ssh remote, and pulls.

XMPP is no longer needed in this configuration!

Requires the remote server have git-annex-shell with notifychanges support.

(untested)

This commit was sponsored by Geog Wechslberger.
This commit is contained in:
Joey Hess 2014-04-08 15:23:50 -04:00
parent cbcb7f50d8
commit fac7bca05b
11 changed files with 150 additions and 7 deletions

View file

@ -21,6 +21,7 @@ import Assistant.Threads.Pusher
import Assistant.Threads.Merger import Assistant.Threads.Merger
import Assistant.Threads.TransferWatcher import Assistant.Threads.TransferWatcher
import Assistant.Threads.Transferrer import Assistant.Threads.Transferrer
import Assistant.Threads.RemoteControl
import Assistant.Threads.SanityChecker import Assistant.Threads.SanityChecker
import Assistant.Threads.Cronner import Assistant.Threads.Cronner
import Assistant.Threads.ProblemFixer import Assistant.Threads.ProblemFixer
@ -147,6 +148,7 @@ startDaemon assistant foreground startdelay cannotrun listenhost startbrowser =
, assist $ transferWatcherThread , assist $ transferWatcherThread
, assist $ transferPollerThread , assist $ transferPollerThread
, assist $ transfererThread , assist $ transfererThread
, assist $ remoteControlThread
, assist $ daemonStatusThread , assist $ daemonStatusThread
, assist $ sanityCheckerDailyThread urlrenderer , assist $ sanityCheckerDailyThread urlrenderer
, assist $ sanityCheckerHourlyThread , assist $ sanityCheckerHourlyThread

View file

@ -16,6 +16,7 @@ import qualified Remote
import Utility.Tense import Utility.Tense
import Logs.Transfer import Logs.Transfer
import Types.Distribution import Types.Distribution
import Git.Types (RemoteName)
import Data.String import Data.String
import qualified Data.Text as T import qualified Data.Text as T
@ -117,11 +118,14 @@ commitAlert :: Alert
commitAlert = activityAlert Nothing commitAlert = activityAlert Nothing
[Tensed "Committing" "Committed", "changes to git"] [Tensed "Committing" "Committed", "changes to git"]
showRemotes :: [Remote] -> TenseChunk showRemotes :: [RemoteName] -> TenseChunk
showRemotes = UnTensed . T.intercalate ", " . map (T.pack . Remote.name) showRemotes = UnTensed . T.intercalate ", " . map T.pack
syncAlert :: [Remote] -> Alert syncAlert :: [Remote] -> Alert
syncAlert rs = baseActivityAlert syncAlert = syncAlert' . map Remote.name
syncAlert' :: [RemoteName] -> Alert
syncAlert' rs = baseActivityAlert
{ alertName = Just SyncAlert { alertName = Just SyncAlert
, alertHeader = Just $ tenseWords , alertHeader = Just $ tenseWords
[Tensed "Syncing" "Synced", "with", showRemotes rs] [Tensed "Syncing" "Synced", "with", showRemotes rs]
@ -130,7 +134,12 @@ syncAlert rs = baseActivityAlert
} }
syncResultAlert :: [Remote] -> [Remote] -> Alert syncResultAlert :: [Remote] -> [Remote] -> Alert
syncResultAlert succeeded failed = makeAlertFiller (not $ null succeeded) $ syncResultAlert succeeded failed = syncResultAlert'
(map Remote.name succeeded)
(map Remote.name failed)
syncResultAlert' :: [RemoteName] -> [RemoteName] -> Alert
syncResultAlert' succeeded failed = makeAlertFiller (not $ null succeeded) $
baseActivityAlert baseActivityAlert
{ alertName = Just SyncAlert { alertName = Just SyncAlert
, alertHeader = Just $ tenseWords msg , alertHeader = Just $ tenseWords msg

View file

@ -43,6 +43,7 @@ import Assistant.Types.RepoProblem
import Assistant.Types.Buddies import Assistant.Types.Buddies
import Assistant.Types.NetMessager import Assistant.Types.NetMessager
import Assistant.Types.ThreadName import Assistant.Types.ThreadName
import Assistant.Types.RemoteControl
newtype Assistant a = Assistant { mkAssistant :: ReaderT AssistantData IO a } newtype Assistant a = Assistant { mkAssistant :: ReaderT AssistantData IO a }
deriving ( deriving (
@ -68,6 +69,7 @@ data AssistantData = AssistantData
, branchChangeHandle :: BranchChangeHandle , branchChangeHandle :: BranchChangeHandle
, buddyList :: BuddyList , buddyList :: BuddyList
, netMessager :: NetMessager , netMessager :: NetMessager
, remoteControl :: RemoteControl
} }
newAssistantData :: ThreadState -> DaemonStatusHandle -> IO AssistantData newAssistantData :: ThreadState -> DaemonStatusHandle -> IO AssistantData
@ -86,6 +88,7 @@ newAssistantData st dstatus = AssistantData
<*> newBranchChangeHandle <*> newBranchChangeHandle
<*> newBuddyList <*> newBuddyList
<*> newNetMessager <*> newNetMessager
<*> newRemoteControl
runAssistant :: AssistantData -> Assistant a -> IO a runAssistant :: AssistantData -> Assistant a -> IO a
runAssistant d a = runReaderT (mkAssistant a) d runAssistant d a = runReaderT (mkAssistant a) d

View file

@ -0,0 +1,21 @@
{- git-annex assistant RemoteDaemon control
-
- Copyright 2014 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU GPL version 3 or higher.
-}
module Assistant.RemoteControl (
sendRemoteControl,
RemoteDaemon.Consumed(..)
) where
import Assistant.Common
import qualified RemoteDaemon.Types as RemoteDaemon
import Control.Concurrent
sendRemoteControl :: RemoteDaemon.Consumed -> Assistant ()
sendRemoteControl msg = do
clicker <- getAssistant remoteControl
liftIO $ writeChan clicker msg

View file

@ -15,6 +15,7 @@ import Assistant.Alert
import Assistant.Alert.Utility import Assistant.Alert.Utility
import Assistant.DaemonStatus import Assistant.DaemonStatus
import Assistant.ScanRemotes import Assistant.ScanRemotes
import Assistant.RemoteControl
import qualified Command.Sync import qualified Command.Sync
import Utility.Parallel import Utility.Parallel
import qualified Git import qualified Git
@ -258,6 +259,7 @@ changeSyncable Nothing enable = do
changeSyncable (Just r) True = do changeSyncable (Just r) True = do
liftAnnex $ changeSyncFlag r True liftAnnex $ changeSyncFlag r True
syncRemote r syncRemote r
sendRemoteControl RELOAD
changeSyncable (Just r) False = do changeSyncable (Just r) False = do
liftAnnex $ changeSyncFlag r False liftAnnex $ changeSyncFlag r False
updateSyncRemotes updateSyncRemotes

View file

@ -15,6 +15,7 @@ import Assistant.Sync
import Utility.ThreadScheduler import Utility.ThreadScheduler
import qualified Types.Remote as Remote import qualified Types.Remote as Remote
import Assistant.DaemonStatus import Assistant.DaemonStatus
import Assistant.RemoteControl
import Utility.NotificationBroadcaster import Utility.NotificationBroadcaster
#if WITH_DBUS #if WITH_DBUS
@ -44,8 +45,9 @@ netWatcherThread = thread noop
- while (despite the local network staying up), are synced with - while (despite the local network staying up), are synced with
- periodically. - periodically.
- -
- Note that it does not call notifyNetMessagerRestart, because - Note that it does not call notifyNetMessagerRestart, or
- it doesn't know that the network has changed. - signal the RemoteControl, because it doesn't know that the
- network has changed.
-} -}
netWatcherFallbackThread :: NamedThread netWatcherFallbackThread :: NamedThread
netWatcherFallbackThread = namedThread "NetWatcherFallback" $ netWatcherFallbackThread = namedThread "NetWatcherFallback" $
@ -69,8 +71,10 @@ dbusThread = do
) )
handleconn = do handleconn = do
debug ["detected network connection"] debug ["detected network connection"]
sendRemoteControl PAUSE
notifyNetMessagerRestart notifyNetMessagerRestart
handleConnection handleConnection
sendRemoteControl RESUME
onerr e _ = do onerr e _ = do
liftAnnex $ liftAnnex $
warning $ "lost dbus connection; falling back to polling (" ++ show e ++ ")" warning $ "lost dbus connection; falling back to polling (" ++ show e ++ ")"

View file

@ -0,0 +1,80 @@
{- git-annex assistant communication with remotedaemon
-
- Copyright 2014 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU GPL version 3 or higher.
-}
module Assistant.Threads.RemoteControl where
import Assistant.Common
import RemoteDaemon.Types
import Config.Files
import Utility.Batch
import Utility.SimpleProtocol
import Assistant.Alert
import Assistant.Alert.Utility
import Assistant.DaemonStatus
import Control.Concurrent
import Control.Concurrent.Async
import System.Process (std_in, std_out)
import qualified Data.Map as M
remoteControlThread :: NamedThread
remoteControlThread = namedThread "RemoteControl" $ do
program <- liftIO readProgramFile
(cmd, params) <- liftIO $ toBatchCommand
(program, [Param "remotedaemon"])
let p = proc cmd (toCommand params)
(Just toh, Just fromh, _, pid) <- liftIO $ createProcess p
{ std_in = CreatePipe
, std_out = CreatePipe
}
controller <- asIO $ remoteControllerThread toh
responder <- asIO $ remoteResponderThread fromh
-- run controller and responder until the remotedaemon dies
liftIO $ do
void $ controller `concurrently` responder
forceSuccessProcess p pid
-- feed from the remoteControl channel into the remotedaemon
remoteControllerThread :: Handle -> Assistant ()
remoteControllerThread toh = do
clicker <- getAssistant remoteControl
liftIO $ forever $ do
msg <- readChan clicker
hPutStrLn toh $ unwords $ formatMessage msg
hFlush toh
-- read status messages emitted by the remotedaemon and handle them
remoteResponderThread :: Handle -> Assistant ()
remoteResponderThread fromh = go M.empty
where
go syncalerts = do
l <- liftIO $ hGetLine fromh
case parseMessage l of
Just (CONNECTED _rn) -> do
go syncalerts
Just (DISCONNECTED _rn) -> do
go syncalerts
Just (SYNCING rn)
| M.member rn syncalerts -> go syncalerts
| otherwise -> do
i <- addAlert $ syncAlert' [rn]
go (M.insert rn i syncalerts)
Just (DONESYNCING status rn) ->
case M.lookup rn syncalerts of
Nothing -> go syncalerts
Just i -> do
let (succeeded, failed) = if status
then ([rn], [])
else ([], [rn])
updateAlertMap $ mergeAlert i $
syncResultAlert' succeeded failed
go (M.delete rn syncalerts)
Nothing -> do
debug ["protocol error from remotedaemon: ", l]
go syncalerts

View file

@ -0,0 +1,16 @@
{- git-annex assistant RemoteDaemon control
-
- Copyright 2014 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU GPL version 3 or higher.
-}
module Assistant.Types.RemoteControl where
import qualified RemoteDaemon.Types as RemoteDaemon
import Control.Concurrent
type RemoteControl = Chan RemoteDaemon.Consumed
newRemoteControl :: IO RemoteControl
newRemoteControl = newChan

4
debian/changelog vendored
View file

@ -2,6 +2,10 @@ git-annex (5.20140406) UNRELEASED; urgency=medium
* importfeed: Filename template can now contain an itempubdate variable. * importfeed: Filename template can now contain an itempubdate variable.
Needs feed 0.3.9.2. Needs feed 0.3.9.2.
* assistant: Now detects immediately when other repositories push
changes to a ssh remote, and pulls.
XMPP is no longer needed in this configuration!
Requires the remote server have git-annex-shell with notifychanges support.
-- Joey Hess <joeyh@debian.org> Mon, 07 Apr 2014 16:22:02 -0400 -- Joey Hess <joeyh@debian.org> Mon, 07 Apr 2014 16:22:02 -0400

View file

@ -83,7 +83,7 @@ Advantages:
exchange protocols implemented in such a daemon to allow SSH-less exchange protocols implemented in such a daemon to allow SSH-less
transfers. transfers.
* Security holes in telehash would not need to compromise the entire * Security holes in telehash would not need to compromise the entire
git-annex. gathd could be sandboxed in one way or another. git-annex. daemon could be sandboxed in one way or another.
Disadvantages: Disadvantages:

View file

@ -167,6 +167,8 @@ TODO:
reconnect, but needs to avoid bad behavior (ie, constant reconnect reconnect, but needs to avoid bad behavior (ie, constant reconnect
attempts.) attempts.)
* Detect if old system had a too old git-annex-shell and avoid bad behavior * Detect if old system had a too old git-annex-shell and avoid bad behavior
* CONNECTED and DISCONNECTED are not wired into any webapp UI; could be
used to show an icon when a ssh remote is available
## telehash ## telehash