diff options
author | Joey Hess <joey@kitenet.net> | 2014-04-06 19:06:03 -0400 |
---|---|---|
committer | Joey Hess <joey@kitenet.net> | 2014-04-06 19:10:23 -0400 |
commit | 8c4bfe2f2141bce84ea22120da445c148b6f1168 (patch) | |
tree | 817f5951cec02c1acec3f26c886beea79cf0957c /RemoteDaemon | |
parent | 1eb96cc31a0f0ec0339f6b28a362b057444069af (diff) |
added git-annex remotedaemon
So far, handling connecting to git-annex-shell notifychanges, and
pulling immediately when a change is pushed to a remote.
A little bit buggy (crashes after the first pull), but it already works!
This commit was sponsored by Mark Sheppard.
Diffstat (limited to 'RemoteDaemon')
-rw-r--r-- | RemoteDaemon/Core.hs | 114 | ||||
-rw-r--r-- | RemoteDaemon/Transport.hs | 21 | ||||
-rw-r--r-- | RemoteDaemon/Transport/Ssh.hs | 75 | ||||
-rw-r--r-- | RemoteDaemon/Transport/Ssh/Types.hs (renamed from RemoteDaemon/EndPoint/GitAnnexShell/Types.hs) | 8 | ||||
-rw-r--r-- | RemoteDaemon/Types.hs | 58 |
5 files changed, 245 insertions, 31 deletions
diff --git a/RemoteDaemon/Core.hs b/RemoteDaemon/Core.hs new file mode 100644 index 000000000..8960bf8d3 --- /dev/null +++ b/RemoteDaemon/Core.hs @@ -0,0 +1,114 @@ +{- git-remote-daemon core + - + - Copyright 2014 Joey Hess <joey@kitenet.net> + - + - Licensed under the GNU GPL version 3 or higher. + -} + +module RemoteDaemon.Core (runForeground) where + +import qualified Annex +import Common +import Types.GitConfig +import RemoteDaemon.Types +import RemoteDaemon.Transport +import qualified Git +import qualified Git.Types as Git +import qualified Git.CurrentRepo +import Utility.SimpleProtocol + +import Control.Concurrent.Async +import Control.Concurrent.Chan +import Network.URI +import qualified Data.Map as M + +runForeground :: IO () +runForeground = do + ichan <- newChan :: IO (Chan Consumed) + ochan <- newChan :: IO (Chan Emitted) + + void $ async $ controller ichan ochan + + let reader = forever $ do + l <- getLine + case parseMessage l of + Nothing -> error $ "protocol error: " ++ l + Just cmd -> writeChan ichan cmd + let writer = forever $ do + msg <- readChan ochan + putStrLn $ unwords $ formatMessage msg + hFlush stdout + + -- If the reader or writer fails, for example because stdin/stdout + -- gets closed, kill the other one, and throw an exception which + -- will take down the daemon. + void $ concurrently reader writer + +type RemoteMap = M.Map Git.Repo (IO (), Chan Consumed) + +-- Runs the transports, dispatching messages to them, and handling +-- the main control messages. +controller :: Chan Consumed -> Chan Emitted -> IO () +controller ichan ochan = do + m <- getRemoteMap ochan + startrunning m + go False m + where + go paused m = do + cmd <- readChan ichan + case cmd of + RELOAD -> do + m' <- getRemoteMap ochan + let common = M.intersection m m' + let new = M.difference m' m + let old = M.difference m m' + stoprunning old + unless paused $ + startrunning new + go paused (M.union common new) + PAUSE -> do + stoprunning m + go True m + RESUME -> do + when paused $ + startrunning m + go False m + STOP -> exitSuccess + -- All remaining messages are sent to + -- all Transports. + msg -> do + unless paused $ + forM_ chans (`writeChan` msg) + go paused m + where + chans = map snd (M.elems m) + + startrunning m = forM_ (M.elems m) startrunning' + startrunning' (transport, _) = void $ async transport + + -- Ask the transport nicely to stop. + stoprunning m = forM_ (M.elems m) stoprunning' + stoprunning' (_, c) = writeChan c STOP + +getRemoteMap :: Chan Emitted -> IO RemoteMap +getRemoteMap ochan = do + annexstate <- Annex.new =<< Git.CurrentRepo.get + genRemoteMap annexstate ochan + +-- Generates a map with a transport for each supported remote in the git repo, +-- except those that have annex.sync = false +genRemoteMap :: Annex.AnnexState -> Chan Emitted -> IO RemoteMap +genRemoteMap annexstate ochan = M.fromList . catMaybes <$> mapM gen rs + where + rs = Git.remotes (Annex.repo annexstate) + gen r = case Git.location r of + Git.Url u -> case M.lookup (uriScheme u) remoteTransports of + Just transport + | remoteAnnexSync (extractRemoteGitConfig r (Git.repoDescribe r)) -> do + ichan <- newChan :: IO (Chan Consumed) + return $ Just + ( r + , (transport r (Git.repoDescribe r) annexstate ichan ochan, ichan) + ) + _ -> return Nothing + _ -> return Nothing diff --git a/RemoteDaemon/Transport.hs b/RemoteDaemon/Transport.hs new file mode 100644 index 000000000..1bac7f877 --- /dev/null +++ b/RemoteDaemon/Transport.hs @@ -0,0 +1,21 @@ +{- git-remote-daemon transports + - + - Copyright 2014 Joey Hess <joey@kitenet.net> + - + - Licensed under the GNU GPL version 3 or higher. + -} + +module RemoteDaemon.Transport where + +import RemoteDaemon.Types +import qualified RemoteDaemon.Transport.Ssh + +import qualified Data.Map as M + +-- Corresponds to uriScheme +type TransportScheme = String + +remoteTransports :: M.Map TransportScheme Transport +remoteTransports = M.fromList + [ ("ssh:", RemoteDaemon.Transport.Ssh.transport) + ] diff --git a/RemoteDaemon/Transport/Ssh.hs b/RemoteDaemon/Transport/Ssh.hs new file mode 100644 index 000000000..8f4d007e8 --- /dev/null +++ b/RemoteDaemon/Transport/Ssh.hs @@ -0,0 +1,75 @@ +{- git-remote-daemon, git-annex-shell over ssh transport + - + - Copyright 2014 Joey Hess <joey@kitenet.net> + - + - Licensed under the GNU GPL version 3 or higher. + -} + +module RemoteDaemon.Transport.Ssh (transport) where + +import Common.Annex +import qualified Annex +import RemoteDaemon.Types +import qualified RemoteDaemon.Transport.Ssh.Types as SshRemote +import Remote.Helper.Ssh +import Utility.SimpleProtocol +import qualified Git +import Annex.CatFile +import Git.Command + +import Control.Concurrent.Chan +import Control.Concurrent.Async +import System.Process (std_in, std_out) + +transport :: Transport +transport r remotename annexstate ichan ochan = Annex.eval annexstate $ do + v <- git_annex_shell r "notifychanges" [] [] + case v of + Nothing -> noop + Just (cmd, params) -> liftIO $ go cmd (toCommand params) + where + send msg = writeChan ochan (msg remotename) + go cmd params = do + (Just toh, Just fromh, _, pid) <- createProcess (proc cmd params) + { std_in = CreatePipe + , std_out = CreatePipe + } + + let shutdown = do + hClose toh + hClose fromh + void $ waitForProcess pid + send DISCONNECTED + + let fromshell = forever $ do + l <- hGetLine fromh + case parseMessage l of + Just SshRemote.READY -> send CONNECTED + Just (SshRemote.CHANGED refs) -> + Annex.eval annexstate $ + fetchNew remotename refs + Nothing -> shutdown + + -- The only control message that matters is STOP. + -- + -- Note that a CHANGED control message is not handled; + -- we don't push to the ssh remote. The assistant + -- and git-annex sync both handle pushes, so there's no + -- need to do it here. + let handlecontrol = forever $ do + msg <- readChan ichan + case msg of + STOP -> ioError (userError "done") + _ -> noop + + -- Run both threads until one finishes. + void $ tryIO $ concurrently fromshell handlecontrol + shutdown + +-- Check if any of the shas are actally new, to avoid unnecessary fetching. +fetchNew :: RemoteName -> [Git.Sha] -> Annex () +fetchNew remotename = check + where + check [] = void $ inRepo $ runBool [Param "fetch", Param remotename] + check (r:rs) = maybe (check rs) (const noop) + =<< catObjectDetails r diff --git a/RemoteDaemon/EndPoint/GitAnnexShell/Types.hs b/RemoteDaemon/Transport/Ssh/Types.hs index 996c4237c..d3fd314b4 100644 --- a/RemoteDaemon/EndPoint/GitAnnexShell/Types.hs +++ b/RemoteDaemon/Transport/Ssh/Types.hs @@ -1,4 +1,4 @@ -{- git-remote-daemon, git-annex-shell endpoint, datatypes +{- git-remote-daemon, git-annex-shell notifychanges protocol types - - Copyright 2014 Joey Hess <joey@kitenet.net> - @@ -8,7 +8,7 @@ {-# LANGUAGE TypeSynonymInstances, FlexibleInstances #-} {-# OPTIONS_GHC -fno-warn-orphans #-} -module RemoteDaemon.EndPoint.GitAnnexShell.Types ( +module RemoteDaemon.Transport.Ssh.Types ( Notification(..), Proto.serialize, Proto.deserialize, @@ -16,11 +16,11 @@ module RemoteDaemon.EndPoint.GitAnnexShell.Types ( ) where import qualified Utility.SimpleProtocol as Proto -import RemoteDaemon.Types (ShaList) +import RemoteDaemon.Types (RefList) data Notification = READY - | CHANGED ShaList + | CHANGED RefList instance Proto.Sendable Notification where formatMessage READY = ["READY"] diff --git a/RemoteDaemon/Types.hs b/RemoteDaemon/Types.hs index b4b8ba066..5cb0ef758 100644 --- a/RemoteDaemon/Types.hs +++ b/RemoteDaemon/Types.hs @@ -10,74 +10,78 @@ module RemoteDaemon.Types where +import qualified Annex import qualified Git.Types as Git import qualified Utility.SimpleProtocol as Proto +import Control.Concurrent + +-- A Transport for a particular git remote consumes some messages +-- from a Chan, and emits others to another Chan. +type Transport = Git.Repo -> RemoteName -> Annex.AnnexState -> Chan Consumed -> Chan Emitted -> IO () + -- Messages that the daemon emits. data Emitted = CONNECTED RemoteName | DISCONNECTED RemoteName - | CHANGED RemoteName ShaList - | STATUS RemoteName UserMessage - | ERROR RemoteName UserMessage + | SYNCING RemoteName + | DONESYNCING RemoteName Bool -- Messages that the deamon consumes. data Consumed = PAUSE | RESUME - | PUSH RemoteName + | CHANGED RefList | RELOAD + | STOP type RemoteName = String -type UserMessage = String -type ShaList = [Git.Sha] +type RefList = [Git.Ref] instance Proto.Sendable Emitted where formatMessage (CONNECTED remote) = ["CONNECTED", Proto.serialize remote] formatMessage (DISCONNECTED remote) = ["DISCONNECTED", Proto.serialize remote] - formatMessage (CHANGED remote shas) = - ["CHANGED" - , Proto.serialize remote - , Proto.serialize shas - ] - formatMessage (STATUS remote msg) = - ["STATUS" - , Proto.serialize remote - , Proto.serialize msg - ] - formatMessage (ERROR remote msg) = - ["ERROR" - , Proto.serialize remote - , Proto.serialize msg - ] + formatMessage (SYNCING remote) = + ["SYNCING", Proto.serialize remote] + formatMessage (DONESYNCING remote status) = + ["DONESYNCING", Proto.serialize remote, Proto.serialize status] instance Proto.Sendable Consumed where formatMessage PAUSE = ["PAUSE"] formatMessage RESUME = ["RESUME"] - formatMessage (PUSH remote) = ["PUSH", Proto.serialize remote] + formatMessage (CHANGED refs) =["CHANGED", Proto.serialize refs] formatMessage RELOAD = ["RELOAD"] + formatMessage STOP = ["STOP"] instance Proto.Receivable Emitted where parseCommand "CONNECTED" = Proto.parse1 CONNECTED parseCommand "DISCONNECTED" = Proto.parse1 DISCONNECTED - parseCommand "CHANGED" = Proto.parse2 CHANGED - parseCommand "STATUS" = Proto.parse2 STATUS - parseCommand "ERROR" = Proto.parse2 ERROR + parseCommand "SYNCING" = Proto.parse1 SYNCING + parseCommand "DONESYNCING" = Proto.parse2 DONESYNCING parseCommand _ = Proto.parseFail instance Proto.Receivable Consumed where parseCommand "PAUSE" = Proto.parse0 PAUSE parseCommand "RESUME" = Proto.parse0 RESUME - parseCommand "PUSH" = Proto.parse1 PUSH + parseCommand "CHANGED" = Proto.parse1 CHANGED parseCommand "RELOAD" = Proto.parse0 RELOAD + parseCommand "STOP" = Proto.parse0 STOP parseCommand _ = Proto.parseFail instance Proto.Serializable [Char] where serialize = id deserialize = Just -instance Proto.Serializable ShaList where +instance Proto.Serializable RefList where serialize = unwords . map Git.fromRef deserialize = Just . map Git.Ref . words + +instance Proto.Serializable Bool where + serialize False = "0" + serialize True = "1" + + deserialize "0" = Just False + deserialize "1" = Just True + deserialize _ = Nothing |