git-annex/RemoteDaemon/Transport/Tor.hs

198 lines
5.4 KiB
Haskell
Raw Normal View History

{- 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
import qualified Annex
import Annex.Concurrent
import Annex.ChangedRefs
2016-11-20 19:45:01 +00:00
import RemoteDaemon.Types
import RemoteDaemon.Common
import Utility.AuthToken
2018-03-06 19:14:53 +00:00
import Utility.Tor
import P2P.Protocol as P2P
import P2P.IO
import P2P.Annex
import P2P.Auth
import P2P.Address
2016-11-20 19:45:01 +00:00
import Annex.UUID
import Types.UUID
import Messages
import Git
import Git.Command
2016-11-20 19:45:01 +00:00
import Control.Concurrent
import System.Log.Logger (debugM)
import Control.Concurrent.STM
import Control.Concurrent.STM.TBMQueue
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.
server :: Server
server ichan th@(TransportHandle (LocalRepo r) _) = go
where
go = checkstartservice >>= handlecontrol
checkstartservice = do
u <- liftAnnex th getUUID
2016-12-30 16:31:17 +00:00
msock <- liftAnnex th torSocketFile
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
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
ok <- atomically $ ifM (isFullTBMQueue q)
( return False
, do
2016-12-24 16:12:58 +00:00
writeTBMQueue q conn
return True
)
unless ok $ do
2016-12-24 16:12:58 +00:00
hClose conn
warningIO "dropped Tor connection, too busy"
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
-- How many clients to serve at a time, maximum. This is to avoid DOS attacks.
maxConnections :: Int
maxConnections = 100
serveClient :: TransportHandle -> UUID -> Repo -> TBMQueue Handle -> IO ()
serveClient th u r q = bracket setup cleanup start
where
setup = do
h <- atomically $ readTBMQueue q
2016-12-08 21:17:01 +00:00
debugM "remotedaemon" "serving a Tor connection"
return h
cleanup Nothing = return ()
cleanup (Just h) = do
debugM "remotedaemon" "done with Tor connection"
hClose h
start Nothing = return ()
start (Just h) = do
-- 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
}
v <- liftIO $ runNetProto conn $ P2P.serveAuth u
case v of
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)
-- Merge the duplicated state back in.
liftAnnex th $ mergeState st'
authed conn theiruuid =
bracket watchChangedRefs (liftIO . maybe noop stopWatchingChangedRefs) $ \crh -> do
runst <- liftIO $ mkRunState (Serving theiruuid crh)
v' <- runFullProto runst conn $
P2P.serveAuthed P2P.ServeReadWrite u
case v' of
Right () -> return ()
Left e -> liftIO $ debugM "remotedaemon" ("Tor connection error: " ++ e)
-- Connect to peer's tor hidden service.
transport :: Transport
transport (RemoteRepo r gc) url@(RemoteURI uri) th ichan ochan =
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)
res <- runNetProto conn $ P2P.auth myuuid authtoken noop
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
_ -> 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
whenM (checkShouldFetch gc th shas) $
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