2016-12-09 20:02:43 +00:00
|
|
|
{- git-remote-daemon, tor hidden service server and transport
|
2016-11-20 19:45:01 +00:00
|
|
|
-
|
|
|
|
- Copyright 2016 Joey Hess <id@joeyh.name>
|
|
|
|
-
|
|
|
|
- Licensed under the GNU GPL version 3 or higher.
|
|
|
|
-}
|
|
|
|
|
2018-03-06 19:14:53 +00:00
|
|
|
{-# LANGUAGE CPP #-}
|
|
|
|
|
|
|
|
module RemoteDaemon.Transport.Tor (server, transport, torSocketFile) where
|
2016-11-20 19:45:01 +00:00
|
|
|
|
|
|
|
import Common
|
2016-12-02 17:50:56 +00:00
|
|
|
import qualified Annex
|
|
|
|
import Annex.Concurrent
|
2016-12-09 19:08:54 +00:00
|
|
|
import Annex.ChangedRefs
|
2016-11-20 19:45:01 +00:00
|
|
|
import RemoteDaemon.Types
|
|
|
|
import RemoteDaemon.Common
|
2016-11-30 20:38:16 +00:00
|
|
|
import Utility.AuthToken
|
2018-03-06 19:14:53 +00:00
|
|
|
import Utility.Tor
|
2016-12-09 20:02:43 +00:00
|
|
|
import P2P.Protocol as P2P
|
2016-12-02 19:34:15 +00:00
|
|
|
import P2P.IO
|
2016-12-02 17:50:56 +00:00
|
|
|
import P2P.Annex
|
2016-11-30 20:38:16 +00:00
|
|
|
import P2P.Auth
|
2016-12-09 20:02:43 +00:00
|
|
|
import P2P.Address
|
2016-11-20 19:45:01 +00:00
|
|
|
import Annex.UUID
|
|
|
|
import Types.UUID
|
2016-11-22 02:03:29 +00:00
|
|
|
import Messages
|
|
|
|
import Git
|
2016-12-09 20:02:43 +00:00
|
|
|
import Git.Command
|
2016-11-20 19:45:01 +00:00
|
|
|
|
|
|
|
import Control.Concurrent
|
|
|
|
import System.Log.Logger (debugM)
|
2016-11-22 02:03:29 +00:00
|
|
|
import Control.Concurrent.STM
|
2016-12-10 15:32:05 +00:00
|
|
|
import Control.Concurrent.STM.TBMQueue
|
2016-12-09 20:02:43 +00:00
|
|
|
import Control.Concurrent.Async
|
2018-03-06 19:14:53 +00:00
|
|
|
#ifndef mingw32_HOST_OS
|
|
|
|
import System.Posix.User
|
|
|
|
#endif
|
2016-11-20 19:45:01 +00:00
|
|
|
|
|
|
|
-- Run tor hidden service.
|
2016-12-28 16:21:52 +00:00
|
|
|
server :: Server
|
|
|
|
server ichan th@(TransportHandle (LocalRepo r) _) = go
|
2016-12-20 20:01:10 +00:00
|
|
|
where
|
2016-12-28 16:21:52 +00:00
|
|
|
go = checkstartservice >>= handlecontrol
|
|
|
|
|
|
|
|
checkstartservice = do
|
|
|
|
u <- liftAnnex th getUUID
|
2016-12-30 16:31:17 +00:00
|
|
|
msock <- liftAnnex th torSocketFile
|
2016-12-28 16:21:52 +00:00
|
|
|
case msock of
|
|
|
|
Nothing -> do
|
|
|
|
debugM "remotedaemon" "Tor hidden service not enabled"
|
|
|
|
return False
|
|
|
|
Just sock -> do
|
|
|
|
void $ async $ startservice sock u
|
|
|
|
return True
|
|
|
|
|
|
|
|
startservice sock u = do
|
2016-12-20 20:01:10 +00:00
|
|
|
q <- newTBMQueueIO maxConnections
|
|
|
|
replicateM_ maxConnections $
|
|
|
|
forkIO $ forever $ serveClient th u r q
|
|
|
|
|
|
|
|
debugM "remotedaemon" "Tor hidden service running"
|
2016-12-24 16:12:58 +00:00
|
|
|
serveUnixSocket sock $ \conn -> do
|
2016-12-20 20:01:10 +00:00
|
|
|
ok <- atomically $ ifM (isFullTBMQueue q)
|
|
|
|
( return False
|
|
|
|
, do
|
2016-12-24 16:12:58 +00:00
|
|
|
writeTBMQueue q conn
|
2016-12-20 20:01:10 +00:00
|
|
|
return True
|
|
|
|
)
|
|
|
|
unless ok $ do
|
2016-12-24 16:12:58 +00:00
|
|
|
hClose conn
|
2016-12-20 20:01:10 +00:00
|
|
|
warningIO "dropped Tor connection, too busy"
|
2016-12-28 16:21:52 +00:00
|
|
|
|
|
|
|
handlecontrol servicerunning = do
|
|
|
|
msg <- atomically $ readTChan ichan
|
|
|
|
case msg of
|
|
|
|
-- On reload, the configuration may have changed to
|
|
|
|
-- enable the tor hidden service. If it was not
|
|
|
|
-- enabled before, start it,
|
|
|
|
RELOAD | not servicerunning -> go
|
|
|
|
-- We can ignore all other messages; no need
|
|
|
|
-- to restart the hidden service when the network
|
|
|
|
-- changes as tor takes care of all that.
|
|
|
|
_ -> handlecontrol servicerunning
|
2016-11-22 02:03:29 +00:00
|
|
|
|
2016-12-09 20:03:25 +00:00
|
|
|
-- How many clients to serve at a time, maximum. This is to avoid DOS attacks.
|
2016-11-22 02:03:29 +00:00
|
|
|
maxConnections :: Int
|
2016-12-09 20:03:25 +00:00
|
|
|
maxConnections = 100
|
2016-11-22 02:03:29 +00:00
|
|
|
|
2016-12-10 15:32:05 +00:00
|
|
|
serveClient :: TransportHandle -> UUID -> Repo -> TBMQueue Handle -> IO ()
|
2016-12-09 19:08:54 +00:00
|
|
|
serveClient th u r q = bracket setup cleanup start
|
2016-11-22 02:03:29 +00:00
|
|
|
where
|
2016-12-09 19:08:54 +00:00
|
|
|
setup = do
|
2016-12-10 15:32:05 +00:00
|
|
|
h <- atomically $ readTBMQueue q
|
2016-12-08 21:17:01 +00:00
|
|
|
debugM "remotedaemon" "serving a Tor connection"
|
2016-12-09 19:08:54 +00:00
|
|
|
return h
|
|
|
|
|
2016-12-10 15:32:05 +00:00
|
|
|
cleanup Nothing = return ()
|
|
|
|
cleanup (Just h) = do
|
2016-12-09 19:08:54 +00:00
|
|
|
debugM "remotedaemon" "done with Tor connection"
|
|
|
|
hClose h
|
|
|
|
|
2016-12-10 15:32:05 +00:00
|
|
|
start Nothing = return ()
|
|
|
|
start (Just h) = do
|
2016-12-02 17:50:56 +00:00
|
|
|
-- Avoid doing any work in the liftAnnex, since only one
|
|
|
|
-- can run at a time.
|
|
|
|
st <- liftAnnex th dupState
|
|
|
|
((), st') <- Annex.run st $ do
|
|
|
|
-- Load auth tokens for every connection, to notice
|
|
|
|
-- when the allowed set is changed.
|
|
|
|
allowed <- loadP2PAuthTokens
|
2016-12-06 19:40:31 +00:00
|
|
|
let conn = P2PConnection
|
|
|
|
{ connRepo = r
|
|
|
|
, connCheckAuth = (`isAllowedAuthToken` allowed)
|
|
|
|
, connIhdl = h
|
|
|
|
, connOhdl = h
|
2016-12-02 17:50:56 +00:00
|
|
|
}
|
2016-12-09 20:02:43 +00:00
|
|
|
v <- liftIO $ runNetProto conn $ P2P.serveAuth u
|
2016-12-02 19:34:15 +00:00
|
|
|
case v of
|
2016-12-09 19:08:54 +00:00
|
|
|
Right (Just theiruuid) -> authed conn theiruuid
|
2016-12-08 19:56:36 +00:00
|
|
|
Right Nothing -> liftIO $
|
2016-12-08 21:17:01 +00:00
|
|
|
debugM "remotedaemon" "Tor connection failed to authenticate"
|
2016-12-08 19:56:36 +00:00
|
|
|
Left e -> liftIO $
|
2016-12-09 17:00:19 +00:00
|
|
|
debugM "remotedaemon" ("Tor connection error before authentication: " ++ e)
|
2016-12-02 17:50:56 +00:00
|
|
|
-- Merge the duplicated state back in.
|
|
|
|
liftAnnex th $ mergeState st'
|
2016-12-09 19:08:54 +00:00
|
|
|
|
|
|
|
authed conn theiruuid =
|
2016-12-09 20:27:20 +00:00
|
|
|
bracket watchChangedRefs (liftIO . maybe noop stopWatchingChangedRefs) $ \crh -> do
|
2018-03-12 17:43:19 +00:00
|
|
|
runst <- liftIO $ mkRunState (Serving theiruuid crh)
|
|
|
|
v' <- runFullProto runst conn $
|
2018-03-07 17:15:55 +00:00
|
|
|
P2P.serveAuthed P2P.ServeReadWrite u
|
2016-12-09 19:08:54 +00:00
|
|
|
case v' of
|
|
|
|
Right () -> return ()
|
|
|
|
Left e -> liftIO $ debugM "remotedaemon" ("Tor connection error: " ++ e)
|
2016-12-09 20:02:43 +00:00
|
|
|
|
|
|
|
-- Connect to peer's tor hidden service.
|
|
|
|
transport :: Transport
|
Added remote.<name>.annex-push and remote.<name>.annex-pull
The former can be useful to make remotes that don't get fully synced with
local changes, which comes up in a lot of situations.
The latter was mostly added for symmetry, but could be useful (though less
likely to be).
Implementing `remote.<name>.annex-pull` was a bit tricky, as there's no one
place where git-annex pulls/fetches from remotes. I audited all
instances of "fetch" and "pull". A few cases were left not checking this
config:
* Git.Repair can try to pull missing refs from a remote, and if the local
repo is corrupted, that seems a reasonable thing to do even though
the config would normally prevent it.
* Assistant.WebApp.Gpg and Remote.Gcrypt and Remote.Git do fetches
as part of the setup process of a remote. The config would probably not
be set then, and having the setup fail seems worse than honoring it if it
is already set.
I have not prevented all the code that does a "merge" from merging branches
from remotes with remote.<name>.annex-pull=false. That could perhaps
be done, but it would need a way to map from branch name to remote name,
and the way refspecs work makes that hard to get really correct. So if the
user fetches manually, the git-annex branch will get merged, for example.
Anther way of looking at/justifying this is that the setting is called
"annex-pull", not "annex-merge".
This commit was supported by the NSF-funded DataLad project.
2017-04-05 17:04:02 +00:00
|
|
|
transport (RemoteRepo r gc) url@(RemoteURI uri) th ichan ochan =
|
2016-12-09 20:02:43 +00:00
|
|
|
case unformatP2PAddress (show uri) of
|
|
|
|
Nothing -> return ()
|
|
|
|
Just addr -> robustConnection 1 $ do
|
|
|
|
g <- liftAnnex th Annex.gitRepo
|
|
|
|
bracket (connectPeer g addr) closeConnection (go addr)
|
|
|
|
where
|
|
|
|
go addr conn = do
|
|
|
|
myuuid <- liftAnnex th getUUID
|
|
|
|
authtoken <- fromMaybe nullAuthToken
|
|
|
|
<$> liftAnnex th (loadP2PRemoteAuthToken addr)
|
2018-03-12 17:43:19 +00:00
|
|
|
res <- runNetProto conn $ P2P.auth myuuid authtoken noop
|
2016-12-09 20:02:43 +00:00
|
|
|
case res of
|
2016-12-09 21:02:21 +00:00
|
|
|
Right (Just theiruuid) -> do
|
|
|
|
expecteduuid <- liftAnnex th $ getRepoUUID r
|
|
|
|
if expecteduuid == theiruuid
|
|
|
|
then do
|
|
|
|
send (CONNECTED url)
|
|
|
|
status <- handlecontrol
|
|
|
|
`race` handlepeer conn
|
|
|
|
send (DISCONNECTED url)
|
|
|
|
return $ either id id status
|
|
|
|
else return ConnectionStopping
|
2016-12-09 20:02:43 +00:00
|
|
|
_ -> return ConnectionClosed
|
|
|
|
|
|
|
|
send msg = atomically $ writeTChan ochan msg
|
|
|
|
|
|
|
|
handlecontrol = do
|
|
|
|
msg <- atomically $ readTChan ichan
|
|
|
|
case msg of
|
|
|
|
STOP -> return ConnectionStopping
|
|
|
|
LOSTNET -> return ConnectionStopping
|
|
|
|
_ -> handlecontrol
|
|
|
|
|
|
|
|
handlepeer conn = do
|
|
|
|
v <- runNetProto conn P2P.notifyChange
|
|
|
|
case v of
|
|
|
|
Right (Just (ChangedRefs shas)) -> do
|
Added remote.<name>.annex-push and remote.<name>.annex-pull
The former can be useful to make remotes that don't get fully synced with
local changes, which comes up in a lot of situations.
The latter was mostly added for symmetry, but could be useful (though less
likely to be).
Implementing `remote.<name>.annex-pull` was a bit tricky, as there's no one
place where git-annex pulls/fetches from remotes. I audited all
instances of "fetch" and "pull". A few cases were left not checking this
config:
* Git.Repair can try to pull missing refs from a remote, and if the local
repo is corrupted, that seems a reasonable thing to do even though
the config would normally prevent it.
* Assistant.WebApp.Gpg and Remote.Gcrypt and Remote.Git do fetches
as part of the setup process of a remote. The config would probably not
be set then, and having the setup fail seems worse than honoring it if it
is already set.
I have not prevented all the code that does a "merge" from merging branches
from remotes with remote.<name>.annex-pull=false. That could perhaps
be done, but it would need a way to map from branch name to remote name,
and the way refspecs work makes that hard to get really correct. So if the
user fetches manually, the git-annex branch will get merged, for example.
Anther way of looking at/justifying this is that the setting is called
"annex-pull", not "annex-merge".
This commit was supported by the NSF-funded DataLad project.
2017-04-05 17:04:02 +00:00
|
|
|
whenM (checkShouldFetch gc th shas) $
|
2016-12-09 20:02:43 +00:00
|
|
|
fetch
|
|
|
|
handlepeer conn
|
|
|
|
_ -> return ConnectionClosed
|
|
|
|
|
|
|
|
fetch = do
|
|
|
|
send (SYNCING url)
|
|
|
|
ok <- inLocalRepo th $
|
|
|
|
runBool [Param "fetch", Param $ Git.repoDescribe r]
|
|
|
|
send (DONESYNCING url ok)
|
2018-03-06 19:14:53 +00:00
|
|
|
|
|
|
|
torSocketFile :: Annex.Annex (Maybe FilePath)
|
|
|
|
torSocketFile = do
|
|
|
|
u <- getUUID
|
|
|
|
let ident = fromUUID u
|
|
|
|
#ifndef mingw32_HOST_OS
|
|
|
|
uid <- liftIO getRealUserID
|
|
|
|
#else
|
|
|
|
let uid = 0
|
|
|
|
#endif
|
|
|
|
liftIO $ getHiddenServiceSocketFile torAppName uid ident
|