remotedaemon: Fork to background by default. Added --foreground switch to enable old behavior.

Groundwork for tor hidden services, which the remotedaemon will serve.
This commit is contained in:
Joey Hess 2016-11-20 14:39:26 -04:00
parent d50b0f3bb3
commit a101b8de37
No known key found for this signature in database
GPG key ID: C910D9222512E3C7
8 changed files with 97 additions and 36 deletions

View file

@ -30,7 +30,7 @@ remoteControlThread :: NamedThread
remoteControlThread = namedThread "RemoteControl" $ do
program <- liftIO programPath
(cmd, params) <- liftIO $ toBatchCommand
(program, [Param "remotedaemon"])
(program, [Param "remotedaemon", Param "--foreground"])
let p = proc cmd (toCommand params)
(Just toh, Just fromh, _, pid) <- liftIO $ createProcess p
{ std_in = CreatePipe

View file

@ -1,3 +1,10 @@
git-annex (6.20161119) UNRELEASED; urgency=medium
* remotedaemon: Fork to background by default. Added --foreground switch
to enable old behavior.
-- Joey Hess <id@joeyh.name> Sun, 20 Nov 2016 14:10:15 -0400
git-annex (6.20161118) unstable; urgency=medium
* git-annex.cabal: Loosen bounds on persistent to allow 2.5, which

View file

@ -14,7 +14,7 @@ import Utility.Tor
-- git-annex, as that would create root-owned files.
cmd :: Command
cmd = noCommit $ dontCheck repoExists $
command "enable-tor" SectionPlumbing ""
command "enable-tor" SectionSetup ""
"userid uuid" (withParams seek)
seek :: CmdParams -> CommandSeek

View file

@ -1,25 +1,32 @@
{- git-annex command
-
- Copyright 2014 Joey Hess <id@joeyh.name>
- Copyright 2014-2016 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU GPL version 3 or higher.
-}
{-# LANGUAGE CPP #-}
module Command.RemoteDaemon where
import Command
import RemoteDaemon.Core
import Utility.Daemon
cmd :: Command
cmd = noCommit $
command "remotedaemon" SectionPlumbing
"detects when remotes have changed, and fetches from them"
paramNothing (withParams seek)
cmd = noCommit $ dontCheck repoExists $
command "remotedaemon" SectionMaintenance
"persistent communication with remotes"
paramNothing (run <$$> const parseDaemonOptions)
seek :: CmdParams -> CommandSeek
seek = withNothing start
start :: CommandStart
start = do
liftIO runForeground
stop
run :: DaemonOptions -> CommandSeek
run o
| stopDaemonOption o = error "--stop not implemented for remotedaemon"
| foregroundDaemonOption o = liftIO runInteractive
| otherwise = do
#ifndef mingw32_HOST_OS
nullfd <- liftIO $ openFd "/dev/null" ReadOnly Nothing defaultFileFlags
liftIO $ daemonize nullfd Nothing False runNonInteractive
#else
liftIO $ foreground Nothing runNonInteractive
#endif

View file

@ -1,11 +1,11 @@
{- git-remote-daemon core
-
- Copyright 2014 Joey Hess <id@joeyh.name>
- Copyright 2014-2016 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU GPL version 3 or higher.
-}
module RemoteDaemon.Core (runForeground) where
module RemoteDaemon.Core (runInteractive, runNonInteractive) where
import qualified Annex
import Common
@ -17,6 +17,7 @@ import qualified Git
import qualified Git.Types as Git
import qualified Git.CurrentRepo
import Utility.SimpleProtocol
import Utility.ThreadScheduler
import Config
import Annex.Ssh
@ -26,8 +27,8 @@ import Control.Concurrent.STM
import Network.URI
import qualified Data.Map as M
runForeground :: IO ()
runForeground = do
runInteractive :: IO ()
runInteractive = do
(readh, writeh) <- dupIoHandles
ichan <- newTChanIO :: IO (TChan Consumed)
ochan <- newTChanIO :: IO (TChan Emitted)
@ -44,8 +45,21 @@ runForeground = do
let controller = runController ichan ochan
-- If any thread fails, the rest will be killed.
void $ tryIO $
reader `concurrently` writer `concurrently` controller
void $ tryIO $ reader `concurrently` writer `concurrently` controller
runNonInteractive :: IO ()
runNonInteractive = do
ichan <- newTChanIO :: IO (TChan Consumed)
ochan <- newTChanIO :: IO (TChan Emitted)
let reader = forever $ do
threadDelaySeconds (Seconds (60*60))
atomically $ writeTChan ichan RELOAD
let writer = forever $
void $ atomically $ readTChan ochan
let controller = runController ichan ochan
void $ tryIO $ reader `concurrently` writer `concurrently` controller
type RemoteMap = M.Map Git.Repo (IO (), TChan Consumed)

View file

@ -14,10 +14,15 @@ It outputs to stdout a line of the form "address.onion:onionport socketfile"
This command has to be run by root, since it modifies `/etc/tor/torrc`.
After this command is run, `git annex remotedaemon` can be run to serve the
hidden service.
# SEE ALSO
[[git-annex]](1)
[[git-annex-remotedaemon]](1)
# AUTHOR
Joey Hess <id@joeyh.name>

View file

@ -1,6 +1,6 @@
# NAME
git-annex remotedaemon - detects when remotes have changed, and fetches from them
git-annex remotedaemon - persistent communication with remotes
# SYNOPSIS
@ -8,18 +8,37 @@ git annex remotedaemon
# DESCRIPTION
This plumbing-level command is used by the assistant to detect
when remotes have received git pushes, so the changes can be promptly
fetched and the local repository updated.
The remotedaemon provides persistent communication with remotes.
This is useful to detect when remotes have received git pushes, so the
changes can be promptly fetched and the local repository updated.
This is a better alternative to the [[git-annex-xmppgit]](1)
hack.
The assistant runs the remotedaemon and communicates with it on
stdio using a simple textual protocol.
For the remotedaemon to work, the git remote must have
[[git-annex-shell]](1) installed, with notifychanges support.
The first version of git-annex-shell that supports it is 5.20140405.
Several types of remotes are supported:
It's normal for this process to be running when the assistant is running.
For ssh remotes, the remotedaemon tries to maintain a connection to the
remote git repository, and uses git-annex-shell notifychanges to detect
when the remote git repository has changed, and fetch the changes from
it. For this to work, the git remote must have [[git-annex-shell]](1)
installed, with notifychanges support. The first version of git-annex-shell
that supports it is 5.20140405.
For tor-annex remotes, the remotedaemon runs as a tor hidden service,
accepting connections from other nodes and serving up the contents of the
repository. This is only done if you first run `git annex enable-tor`.
# OPTIONS
* `--foreground`
Don't fork to the background, and communicate on stdin/stdout using a
simple textual protocol. The assistant runs the remotedaemon this way.
Commands in the protocol include LOSTNET, which tells the remotedaemon
that the network connection has been lost, and causes it to stop any TCP
connctions. That can be followed by RESUME when the network connection
comes back up.
# SEE ALSO
@ -27,6 +46,8 @@ It's normal for this process to be running when the assistant is running.
[[git-annex-assistant]](1)
[[git-annex-enable-tor]](1)
# AUTHOR
Joey Hess <id@joeyh.name>

View file

@ -212,6 +212,12 @@ subdirectories).
See [[git-annex-enableremote]](1) for details.
* `enable-tor`
Sets up tor hidden service.
See [[git-annex-enable-tor]](1) for details.
* `numcopies [N]`
Configure desired number of copies.
@ -379,6 +385,13 @@ subdirectories).
See [[git-annex-repair]](1) for details.
* `remotedaemon`
Persistent communication with remotes.
See [[git-annex-remotedaemon]](1) for details.
# QUERY COMMANDS
* `find [path ...]`
@ -652,12 +665,6 @@ subdirectories).
See [[git-annex-smudge]](1) for details.
* `remotedaemon`
Detects when network remotes have received git pushes and fetches from them.
See [[git-annex-remotedaemon]](1) for details.
* `xmppgit`
This command is used internally by the assistant to perform git pulls