This commit is contained in:
Joey Hess 2016-12-06 15:40:31 -04:00
parent 26a53fb4a5
commit f744bd5391
No known key found for this signature in database
GPG key ID: C910D9222512E3C7
7 changed files with 74 additions and 86 deletions

View file

@ -12,7 +12,6 @@ import qualified Annex
import qualified Git.CurrentRepo import qualified Git.CurrentRepo
import P2P.Protocol import P2P.Protocol
import P2P.IO import P2P.IO
import Remote.Helper.Tor
import Utility.Tor import Utility.Tor
import Utility.AuthToken import Utility.AuthToken
import Annex.UUID import Annex.UUID
@ -59,14 +58,8 @@ connectService address port service = do
<$> loadP2PRemoteAuthToken (TorAnnex address port) <$> loadP2PRemoteAuthToken (TorAnnex address port)
myuuid <- getUUID myuuid <- getUUID
g <- Annex.gitRepo g <- Annex.gitRepo
h <- liftIO $ torHandle =<< connectHiddenService address port conn <- liftIO $ connectPeer g (TorAnnex address port)
let runenv = RunEnv liftIO $ runNetProto conn $ do
{ runRepo = g
, runCheckAuth = const False
, runIhdl = h
, runOhdl = h
}
liftIO $ runNetProto runenv $ do
v <- auth myuuid authtoken v <- auth myuuid authtoken
case v of case v of
Just _theiruuid -> connect service stdin stdout Just _theiruuid -> connect service stdin stdout

View file

@ -9,7 +9,7 @@
module P2P.Annex module P2P.Annex
( RunMode(..) ( RunMode(..)
, RunEnv(..) , P2PConnection(..)
, runFullProto , runFullProto
) where ) where
@ -31,12 +31,12 @@ data RunMode
| Client | Client
-- Full interpreter for Proto, that can receive and send objects. -- Full interpreter for Proto, that can receive and send objects.
runFullProto :: RunMode -> RunEnv -> Proto a -> Annex (Maybe a) runFullProto :: RunMode -> P2PConnection -> Proto a -> Annex (Maybe a)
runFullProto runmode runenv = go runFullProto runmode conn = go
where where
go :: RunProto Annex go :: RunProto Annex
go (Pure v) = pure (Just v) go (Pure v) = pure (Just v)
go (Free (Net n)) = runNet runenv go n go (Free (Net n)) = runNet conn go n
go (Free (Local l)) = runLocal runmode go l go (Free (Local l)) = runLocal runmode go l
runLocal :: RunMode -> RunProto Annex -> LocalF (Proto a) -> Annex (Maybe a) runLocal :: RunMode -> RunProto Annex -> LocalF (Proto a) -> Annex (Maybe a)

View file

@ -9,12 +9,15 @@
module P2P.IO module P2P.IO
( RunProto ( RunProto
, RunEnv(..) , P2PConnection(..)
, connectPeer
, setupHandle
, runNetProto , runNetProto
, runNet , runNet
) where ) where
import P2P.Protocol import P2P.Protocol
import P2P.Address
import Utility.Process import Utility.Process
import Git import Git
import Git.Command import Git.Command
@ -22,11 +25,14 @@ import Utility.AuthToken
import Utility.SafeCommand import Utility.SafeCommand
import Utility.SimpleProtocol import Utility.SimpleProtocol
import Utility.Exception import Utility.Exception
import Utility.Tor
import Utility.FileSystemEncoding
import Control.Monad import Control.Monad
import Control.Monad.Free import Control.Monad.Free
import Control.Monad.IO.Class import Control.Monad.IO.Class
import System.Exit (ExitCode(..)) import System.Exit (ExitCode(..))
import Network.Socket
import System.IO import System.IO
import Control.Concurrent import Control.Concurrent
import Control.Concurrent.Async import Control.Concurrent.Async
@ -36,41 +42,60 @@ import qualified Data.ByteString.Lazy as L
-- Type of interpreters of the Proto free monad. -- Type of interpreters of the Proto free monad.
type RunProto m = forall a. (MonadIO m, MonadMask m) => Proto a -> m (Maybe a) type RunProto m = forall a. (MonadIO m, MonadMask m) => Proto a -> m (Maybe a)
data RunEnv = RunEnv data P2PConnection = P2PConnection
{ runRepo :: Repo { connRepo :: Repo
, runCheckAuth :: (AuthToken -> Bool) , connCheckAuth :: (AuthToken -> Bool)
, runIhdl :: Handle , connIhdl :: Handle
, runOhdl :: Handle , connOhdl :: Handle
} }
-- Opens a connection to a peer. Does not authenticate with it.
connectPeer :: Git.Repo -> P2PAddress -> IO P2PConnection
connectPeer g (TorAnnex onionaddress onionport) = do
h <- setupHandle =<< connectHiddenService onionaddress onionport
return $ P2PConnection
{ connRepo = g
, connCheckAuth = const False
, connIhdl = h
, connOhdl = h
}
setupHandle :: Socket -> IO Handle
setupHandle s = do
h <- socketToHandle s ReadWriteMode
hSetBuffering h LineBuffering
hSetBinaryMode h False
fileEncoding h
return h
-- Purposefully incomplete interpreter of Proto. -- Purposefully incomplete interpreter of Proto.
-- --
-- This only runs Net actions. No Local actions will be run -- This only runs Net actions. No Local actions will be run
-- (those need the Annex monad) -- if the interpreter reaches any, -- (those need the Annex monad) -- if the interpreter reaches any,
-- it returns Nothing. -- it returns Nothing.
runNetProto :: RunEnv -> Proto a -> IO (Maybe a) runNetProto :: P2PConnection -> Proto a -> IO (Maybe a)
runNetProto runenv = go runNetProto conn = go
where where
go :: RunProto IO go :: RunProto IO
go (Pure v) = pure (Just v) go (Pure v) = pure (Just v)
go (Free (Net n)) = runNet runenv go n go (Free (Net n)) = runNet conn go n
go (Free (Local _)) = return Nothing go (Free (Local _)) = return Nothing
-- Interpreter of the Net part of Proto. -- Interpreter of the Net part of Proto.
-- --
-- An interpreter of Proto has to be provided, to handle the rest of Proto -- An interpreter of Proto has to be provided, to handle the rest of Proto
-- actions. -- actions.
runNet :: (MonadIO m, MonadMask m) => RunEnv -> RunProto m -> NetF (Proto a) -> m (Maybe a) runNet :: (MonadIO m, MonadMask m) => P2PConnection -> RunProto m -> NetF (Proto a) -> m (Maybe a)
runNet runenv runner f = case f of runNet conn runner f = case f of
SendMessage m next -> do SendMessage m next -> do
v <- liftIO $ tryNonAsync $ do v <- liftIO $ tryNonAsync $ do
hPutStrLn (runOhdl runenv) (unwords (formatMessage m)) hPutStrLn (connOhdl conn) (unwords (formatMessage m))
hFlush (runOhdl runenv) hFlush (connOhdl conn)
case v of case v of
Left _e -> return Nothing Left _e -> return Nothing
Right () -> runner next Right () -> runner next
ReceiveMessage next -> do ReceiveMessage next -> do
v <- liftIO $ tryNonAsync $ hGetLine (runIhdl runenv) v <- liftIO $ tryNonAsync $ hGetLine (connIhdl conn)
case v of case v of
Left _e -> return Nothing Left _e -> return Nothing
Right l -> case parseMessage l of Right l -> case parseMessage l of
@ -81,19 +106,19 @@ runNet runenv runner f = case f of
next e next e
SendBytes len b next -> do SendBytes len b next -> do
v <- liftIO $ tryNonAsync $ do v <- liftIO $ tryNonAsync $ do
ok <- sendExactly len b (runOhdl runenv) ok <- sendExactly len b (connOhdl conn)
hFlush (runOhdl runenv) hFlush (connOhdl conn)
return ok return ok
case v of case v of
Right True -> runner next Right True -> runner next
_ -> return Nothing _ -> return Nothing
ReceiveBytes (Len n) next -> do ReceiveBytes (Len n) next -> do
v <- liftIO $ tryNonAsync $ L.hGet (runIhdl runenv) (fromIntegral n) v <- liftIO $ tryNonAsync $ L.hGet (connIhdl conn) (fromIntegral n)
case v of case v of
Left _e -> return Nothing Left _e -> return Nothing
Right b -> runner (next b) Right b -> runner (next b)
CheckAuthToken _u t next -> do CheckAuthToken _u t next -> do
let authed = runCheckAuth runenv t let authed = connCheckAuth conn t
runner (next authed) runner (next authed)
Relay hin hout next -> do Relay hin hout next -> do
v <- liftIO $ runRelay runnerio hin hout v <- liftIO $ runRelay runnerio hin hout
@ -101,7 +126,7 @@ runNet runenv runner f = case f of
Nothing -> return Nothing Nothing -> return Nothing
Just exitcode -> runner (next exitcode) Just exitcode -> runner (next exitcode)
RelayService service next -> do RelayService service next -> do
v <- liftIO $ runRelayService runenv runnerio service v <- liftIO $ runRelayService conn runnerio service
case v of case v of
Nothing -> return Nothing Nothing -> return Nothing
Just () -> runner next Just () -> runner next
@ -109,7 +134,7 @@ runNet runenv runner f = case f of
-- This is only used for running Net actions when relaying, -- This is only used for running Net actions when relaying,
-- so it's ok to use runNetProto, despite it not supporting -- so it's ok to use runNetProto, despite it not supporting
-- all Proto actions. -- all Proto actions.
runnerio = runNetProto runenv runnerio = runNetProto conn
-- Send exactly the specified number of bytes or returns False. -- Send exactly the specified number of bytes or returns False.
-- --
@ -150,8 +175,8 @@ runRelay runner (RelayHandle hout) (RelayHandle hin) = bracket setup cleanup go
go v = relayHelper runner v hin go v = relayHelper runner v hin
runRelayService :: RunEnv -> RunProto IO -> Service -> IO (Maybe ()) runRelayService :: P2PConnection -> RunProto IO -> Service -> IO (Maybe ())
runRelayService runenv runner service = bracket setup cleanup go runRelayService conn runner service = bracket setup cleanup go
where where
cmd = case service of cmd = case service of
UploadPack -> "upload-pack" UploadPack -> "upload-pack"
@ -159,8 +184,8 @@ runRelayService runenv runner service = bracket setup cleanup go
serviceproc = gitCreateProcess serviceproc = gitCreateProcess
[ Param cmd [ Param cmd
, File (repoPath (runRepo runenv)) , File (repoPath (connRepo conn))
] (runRepo runenv) ] (connRepo conn)
setup = do setup = do
(Just hin, Just hout, _, pid) <- createProcess serviceproc (Just hin, Just hout, _, pid) <- createProcess serviceproc

View file

@ -1,20 +0,0 @@
{- Helpers for tor remotes.
-
- Copyright 2016 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU GPL version 3 or higher.
-}
module Remote.Helper.Tor where
import Annex.Common
import Network.Socket
torHandle :: Socket -> IO Handle
torHandle s = do
h <- socketToHandle s ReadWriteMode
hSetBuffering h LineBuffering
hSetBinaryMode h False
fileEncoding h
return h

View file

@ -15,14 +15,13 @@ import qualified Annex
import qualified P2P.Protocol as P2P import qualified P2P.Protocol as P2P
import P2P.Address import P2P.Address
import P2P.Annex import P2P.Annex
import P2P.IO
import Types.Remote import Types.Remote
import Types.GitConfig import Types.GitConfig
import qualified Git import qualified Git
import Config import Config
import Config.Cost import Config.Cost
import Remote.Helper.Git import Remote.Helper.Git
import Remote.Helper.Tor
import Utility.Tor
import Utility.Metered import Utility.Metered
import Types.NumCopies import Types.NumCopies
@ -108,7 +107,7 @@ lock theiruuid addr connpool k callback =
-- | A connection to the peer. -- | A connection to the peer.
data Connection data Connection
= TorAnnexConnection RunEnv = OpenConnection P2PConnection
| ClosedConnection | ClosedConnection
type ConnectionPool = TVar [Connection] type ConnectionPool = TVar [Connection]
@ -122,14 +121,15 @@ runProto addr connpool a = withConnection addr connpool (runProto' a)
runProto' :: P2P.Proto a -> Connection -> Annex (Connection, Maybe a) runProto' :: P2P.Proto a -> Connection -> Annex (Connection, Maybe a)
runProto' _ ClosedConnection = return (ClosedConnection, Nothing) runProto' _ ClosedConnection = return (ClosedConnection, Nothing)
runProto' a conn@(TorAnnexConnection runenv) = do runProto' a (OpenConnection conn) = do
r <- runFullProto Client runenv a r <- runFullProto Client conn a
-- When runFullProto fails, the connection is no longer usable, -- When runFullProto fails, the connection is no longer usable,
-- so close it. -- so close it.
if isJust r if isJust r
then return (conn, r) then return (OpenConnection conn, r)
else do else do
liftIO $ hClose (runIhdl runenv) liftIO $ hClose (connIhdl conn)
liftIO $ hClose (connOhdl conn)
return (ClosedConnection, r) return (ClosedConnection, r)
-- Uses an open connection if one is available in the ConnectionPool; -- Uses an open connection if one is available in the ConnectionPool;
@ -161,17 +161,9 @@ withConnection addr connpool a = bracketOnError get cache go
return r return r
openConnection :: P2PAddress -> Annex Connection openConnection :: P2PAddress -> Annex Connection
openConnection (TorAnnex onionaddress onionport) = do openConnection addr = do
v <- liftIO $ tryNonAsync $ g <- Annex.gitRepo
torHandle =<< connectHiddenService onionaddress onionport v <- liftIO $ tryNonAsync $ connectPeer g addr
case v of case v of
Right h -> do Right conn -> return (OpenConnection conn)
g <- Annex.gitRepo
let runenv = RunEnv
{ runRepo = g
, runCheckAuth = const False
, runIhdl = h
, runOhdl = h
}
return (TorAnnexConnection runenv)
Left _e -> return ClosedConnection Left _e -> return ClosedConnection

View file

@ -15,7 +15,6 @@ import RemoteDaemon.Common
import Utility.Tor import Utility.Tor
import Utility.FileMode import Utility.FileMode
import Utility.AuthToken import Utility.AuthToken
import Remote.Helper.Tor
import P2P.Protocol import P2P.Protocol
import P2P.IO import P2P.IO
import P2P.Annex import P2P.Annex
@ -55,7 +54,7 @@ server th@(TransportHandle (LocalRepo r) _) = do
debugM "remotedaemon" "tor hidden service running" debugM "remotedaemon" "tor hidden service running"
forever $ do forever $ do
(conn, _) <- accept soc (conn, _) <- accept soc
h <- torHandle conn h <- setupHandle conn
ok <- atomically $ ifM (isFullTBQueue q) ok <- atomically $ ifM (isFullTBQueue q)
( return False ( return False
, do , do
@ -85,16 +84,16 @@ serveClient th u r q = bracket setup cleanup go
-- Load auth tokens for every connection, to notice -- Load auth tokens for every connection, to notice
-- when the allowed set is changed. -- when the allowed set is changed.
allowed <- loadP2PAuthTokens allowed <- loadP2PAuthTokens
let runenv = RunEnv let conn = P2PConnection
{ runRepo = r { connRepo = r
, runCheckAuth = (`isAllowedAuthToken` allowed) , connCheckAuth = (`isAllowedAuthToken` allowed)
, runIhdl = h , connIhdl = h
, runOhdl = h , connOhdl = h
} }
v <- liftIO $ runNetProto runenv $ serveAuth u v <- liftIO $ runNetProto conn $ serveAuth u
case v of case v of
Just (Just theiruuid) -> void $ Just (Just theiruuid) -> void $
runFullProto (Serving theiruuid) runenv $ runFullProto (Serving theiruuid) conn $
serveAuthed u serveAuthed u
_ -> return () _ -> return ()
-- Merge the duplicated state back in. -- Merge the duplicated state back in.

View file

@ -934,7 +934,6 @@ Executable git-annex
Remote.Helper.ReadOnly Remote.Helper.ReadOnly
Remote.Helper.Special Remote.Helper.Special
Remote.Helper.Ssh Remote.Helper.Ssh
Remote.Helper.Tor
Remote.Hook Remote.Hook
Remote.List Remote.List
Remote.P2P Remote.P2P