2016-12-01 04:41:01 +00:00
|
|
|
{- P2P protocol, IO implementation
|
2016-11-20 16:08:16 +00:00
|
|
|
-
|
2024-07-01 14:04:45 +00:00
|
|
|
- Copyright 2016-2024 Joey Hess <id@joeyh.name>
|
2016-11-20 16:08:16 +00:00
|
|
|
-
|
2019-03-13 19:48:14 +00:00
|
|
|
- Licensed under the GNU AGPL version 3 or higher.
|
2016-11-20 16:08:16 +00:00
|
|
|
-}
|
|
|
|
|
2021-04-05 17:40:31 +00:00
|
|
|
{-# LANGUAGE RankNTypes, FlexibleContexts, OverloadedStrings, CPP #-}
|
2016-11-20 16:08:16 +00:00
|
|
|
|
2016-11-22 18:34:49 +00:00
|
|
|
module P2P.IO
|
2016-12-02 17:45:45 +00:00
|
|
|
( RunProto
|
2018-03-12 19:19:40 +00:00
|
|
|
, RunState(..)
|
|
|
|
, mkRunState
|
2024-06-28 15:22:29 +00:00
|
|
|
, P2PHandle(..)
|
2016-12-06 19:40:31 +00:00
|
|
|
, P2PConnection(..)
|
2018-10-22 19:52:11 +00:00
|
|
|
, ConnIdent(..)
|
2018-03-08 18:02:18 +00:00
|
|
|
, ClosableConnection(..)
|
2018-03-07 19:15:23 +00:00
|
|
|
, stdioP2PConnection
|
2024-07-01 14:04:45 +00:00
|
|
|
, stdioP2PConnectionDupped
|
2016-12-06 19:40:31 +00:00
|
|
|
, connectPeer
|
2016-12-06 19:49:39 +00:00
|
|
|
, closeConnection
|
2016-12-24 16:12:58 +00:00
|
|
|
, serveUnixSocket
|
2016-12-06 19:40:31 +00:00
|
|
|
, setupHandle
|
2018-09-25 20:49:59 +00:00
|
|
|
, ProtoFailure(..)
|
|
|
|
, describeProtoFailure
|
2016-12-01 04:41:01 +00:00
|
|
|
, runNetProto
|
|
|
|
, runNet
|
2024-07-11 13:55:17 +00:00
|
|
|
, signalFullyConsumedByteString
|
2016-11-20 16:08:16 +00:00
|
|
|
) where
|
|
|
|
|
2016-12-24 16:12:58 +00:00
|
|
|
import Common
|
2016-11-24 20:36:16 +00:00
|
|
|
import P2P.Protocol
|
2016-12-06 19:40:31 +00:00
|
|
|
import P2P.Address
|
2016-11-20 16:08:16 +00:00
|
|
|
import Git
|
|
|
|
import Git.Command
|
2016-11-30 20:38:16 +00:00
|
|
|
import Utility.AuthToken
|
2016-11-20 16:08:16 +00:00
|
|
|
import Utility.SimpleProtocol
|
2016-12-07 17:37:35 +00:00
|
|
|
import Utility.Metered
|
2016-12-06 19:40:31 +00:00
|
|
|
import Utility.Tor
|
2016-12-24 16:12:58 +00:00
|
|
|
import Utility.FileMode
|
2021-04-05 17:40:31 +00:00
|
|
|
import Utility.Debug
|
2024-07-03 21:54:01 +00:00
|
|
|
import Utility.MonotonicClock
|
2018-03-12 19:19:40 +00:00
|
|
|
import Types.UUID
|
|
|
|
import Annex.ChangedRefs
|
2020-11-24 16:38:12 +00:00
|
|
|
import qualified Utility.RawFilePath as R
|
2016-11-20 16:08:16 +00:00
|
|
|
|
|
|
|
import Control.Monad.Free
|
|
|
|
import Control.Monad.IO.Class
|
2018-09-25 20:49:59 +00:00
|
|
|
import System.IO.Error
|
2016-12-06 19:40:31 +00:00
|
|
|
import Network.Socket
|
2016-11-20 16:08:16 +00:00
|
|
|
import Control.Concurrent
|
2016-11-21 23:24:55 +00:00
|
|
|
import Control.Concurrent.Async
|
2018-03-12 19:19:40 +00:00
|
|
|
import Control.Concurrent.STM
|
2016-11-20 16:08:16 +00:00
|
|
|
import qualified Data.ByteString as B
|
|
|
|
import qualified Data.ByteString.Lazy as L
|
2016-12-24 16:12:58 +00:00
|
|
|
import qualified Network.Socket as S
|
2023-03-01 19:55:58 +00:00
|
|
|
import System.PosixCompat.Files (groupReadMode, groupWriteMode, otherReadMode, otherWriteMode)
|
2016-11-20 16:08:16 +00:00
|
|
|
|
2016-12-01 03:54:00 +00:00
|
|
|
-- Type of interpreters of the Proto free monad.
|
2018-09-25 20:49:59 +00:00
|
|
|
type RunProto m = forall a. Proto a -> m (Either ProtoFailure a)
|
|
|
|
|
|
|
|
data ProtoFailure
|
|
|
|
= ProtoFailureMessage String
|
|
|
|
| ProtoFailureException SomeException
|
|
|
|
| ProtoFailureIOError IOError
|
2024-07-26 14:24:23 +00:00
|
|
|
deriving (Show)
|
2018-09-25 20:49:59 +00:00
|
|
|
|
|
|
|
describeProtoFailure :: ProtoFailure -> String
|
|
|
|
describeProtoFailure (ProtoFailureMessage s) = s
|
|
|
|
describeProtoFailure (ProtoFailureException e) = show e
|
|
|
|
describeProtoFailure (ProtoFailureIOError e) = show e
|
2016-11-20 16:08:16 +00:00
|
|
|
|
2018-03-12 19:19:40 +00:00
|
|
|
data RunState
|
|
|
|
= Serving UUID (Maybe ChangedRefsHandle) (TVar ProtocolVersion)
|
|
|
|
| Client (TVar ProtocolVersion)
|
|
|
|
|
|
|
|
mkRunState :: (TVar ProtocolVersion -> RunState) -> IO RunState
|
|
|
|
mkRunState mk = do
|
|
|
|
tvar <- newTVarIO defaultProtocolVersion
|
|
|
|
return (mk tvar)
|
|
|
|
|
2024-06-28 15:22:29 +00:00
|
|
|
data P2PHandle
|
|
|
|
= P2PHandle Handle
|
2024-07-26 19:25:15 +00:00
|
|
|
| P2PHandleTMVar
|
|
|
|
(TMVar (Either L.ByteString Message))
|
|
|
|
(Maybe (TMVar ()))
|
|
|
|
(TMVar ())
|
2024-07-11 13:55:17 +00:00
|
|
|
|
|
|
|
signalFullyConsumedByteString :: P2PHandle -> IO ()
|
|
|
|
signalFullyConsumedByteString (P2PHandle _) = return ()
|
2024-07-26 19:25:15 +00:00
|
|
|
signalFullyConsumedByteString (P2PHandleTMVar _ Nothing _) = return ()
|
|
|
|
signalFullyConsumedByteString (P2PHandleTMVar _ (Just waitv) closedv) =
|
2024-07-11 13:55:17 +00:00
|
|
|
atomically $ putTMVar waitv ()
|
2024-07-26 19:25:15 +00:00
|
|
|
`orElse` readTMVar closedv
|
2024-06-28 15:22:29 +00:00
|
|
|
|
2016-12-06 19:40:31 +00:00
|
|
|
data P2PConnection = P2PConnection
|
git-annex-shell: block relay requests
connRepo is only used when relaying git upload-pack and receive-pack.
That's only supposed to be used when git-annex-remotedaemon is serving
git-remote-tor-annex connections over tor. But, it was always set, and
so could be used in other places possibly.
Fixed by making connRepo optional in the P2P protocol interface.
In Command.EnableTor, it's not needed, because it only speaks the
protocol in order to check that it's able to connect back to itself via
the hidden service. So changed that to pass Nothing rather than the git
repo.
In Remote.Helper.Ssh, it's connecting to git-annex-shell p2pstdio,
so is making the requests, so will never need connRepo.
In git-annex-shell p2pstdio, it was accepting git upload-pack and
receive-pack requests over the P2P protocol, even though nothing sent
them. This is arguably a security hole, particularly if the user has
set environment variables like GIT_ANNEX_SHELL_LIMITED to prevent
git push/pull via git-annex-shell.
2024-06-10 17:53:28 +00:00
|
|
|
{ connRepo :: Maybe Repo
|
2016-12-06 19:40:31 +00:00
|
|
|
, connCheckAuth :: (AuthToken -> Bool)
|
2024-06-28 15:22:29 +00:00
|
|
|
, connIhdl :: P2PHandle
|
|
|
|
, connOhdl :: P2PHandle
|
2018-10-22 19:52:11 +00:00
|
|
|
, connIdent :: ConnIdent
|
2016-11-20 16:08:16 +00:00
|
|
|
}
|
|
|
|
|
2018-10-22 19:52:11 +00:00
|
|
|
-- Identifier for a connection, only used for debugging.
|
|
|
|
newtype ConnIdent = ConnIdent (Maybe String)
|
2024-07-26 19:25:15 +00:00
|
|
|
deriving (Show)
|
2018-10-22 19:52:11 +00:00
|
|
|
|
2018-03-08 18:02:18 +00:00
|
|
|
data ClosableConnection conn
|
|
|
|
= OpenConnection conn
|
|
|
|
| ClosedConnection
|
|
|
|
|
2018-03-07 19:15:23 +00:00
|
|
|
-- P2PConnection using stdio.
|
git-annex-shell: block relay requests
connRepo is only used when relaying git upload-pack and receive-pack.
That's only supposed to be used when git-annex-remotedaemon is serving
git-remote-tor-annex connections over tor. But, it was always set, and
so could be used in other places possibly.
Fixed by making connRepo optional in the P2P protocol interface.
In Command.EnableTor, it's not needed, because it only speaks the
protocol in order to check that it's able to connect back to itself via
the hidden service. So changed that to pass Nothing rather than the git
repo.
In Remote.Helper.Ssh, it's connecting to git-annex-shell p2pstdio,
so is making the requests, so will never need connRepo.
In git-annex-shell p2pstdio, it was accepting git upload-pack and
receive-pack requests over the P2P protocol, even though nothing sent
them. This is arguably a security hole, particularly if the user has
set environment variables like GIT_ANNEX_SHELL_LIMITED to prevent
git push/pull via git-annex-shell.
2024-06-10 17:53:28 +00:00
|
|
|
stdioP2PConnection :: Maybe Git.Repo -> P2PConnection
|
2018-03-07 19:15:23 +00:00
|
|
|
stdioP2PConnection g = P2PConnection
|
|
|
|
{ connRepo = g
|
|
|
|
, connCheckAuth = const False
|
2024-06-28 15:22:29 +00:00
|
|
|
, connIhdl = P2PHandle stdin
|
|
|
|
, connOhdl = P2PHandle stdout
|
2018-10-22 19:52:11 +00:00
|
|
|
, connIdent = ConnIdent Nothing
|
2018-03-07 19:15:23 +00:00
|
|
|
}
|
|
|
|
|
2024-07-01 14:04:45 +00:00
|
|
|
-- P2PConnection using stdio, but with the handles first duplicated,
|
|
|
|
-- to avoid anything that might output to stdio (eg a program run by a
|
|
|
|
-- special remote) from interfering with the connection.
|
|
|
|
stdioP2PConnectionDupped :: Maybe Git.Repo -> IO P2PConnection
|
|
|
|
stdioP2PConnectionDupped g = do
|
|
|
|
(readh, writeh) <- dupIoHandles
|
|
|
|
return $ P2PConnection
|
|
|
|
{ connRepo = g
|
|
|
|
, connCheckAuth = const False
|
|
|
|
, connIhdl = P2PHandle readh
|
|
|
|
, connOhdl = P2PHandle writeh
|
|
|
|
, connIdent = ConnIdent Nothing
|
|
|
|
}
|
|
|
|
|
2016-12-06 19:40:31 +00:00
|
|
|
-- Opens a connection to a peer. Does not authenticate with it.
|
git-annex-shell: block relay requests
connRepo is only used when relaying git upload-pack and receive-pack.
That's only supposed to be used when git-annex-remotedaemon is serving
git-remote-tor-annex connections over tor. But, it was always set, and
so could be used in other places possibly.
Fixed by making connRepo optional in the P2P protocol interface.
In Command.EnableTor, it's not needed, because it only speaks the
protocol in order to check that it's able to connect back to itself via
the hidden service. So changed that to pass Nothing rather than the git
repo.
In Remote.Helper.Ssh, it's connecting to git-annex-shell p2pstdio,
so is making the requests, so will never need connRepo.
In git-annex-shell p2pstdio, it was accepting git upload-pack and
receive-pack requests over the P2P protocol, even though nothing sent
them. This is arguably a security hole, particularly if the user has
set environment variables like GIT_ANNEX_SHELL_LIMITED to prevent
git push/pull via git-annex-shell.
2024-06-10 17:53:28 +00:00
|
|
|
connectPeer :: Maybe Git.Repo -> P2PAddress -> IO P2PConnection
|
2016-12-06 19:40:31 +00:00
|
|
|
connectPeer g (TorAnnex onionaddress onionport) = do
|
|
|
|
h <- setupHandle =<< connectHiddenService onionaddress onionport
|
|
|
|
return $ P2PConnection
|
|
|
|
{ connRepo = g
|
|
|
|
, connCheckAuth = const False
|
2024-06-28 15:22:29 +00:00
|
|
|
, connIhdl = P2PHandle h
|
|
|
|
, connOhdl = P2PHandle h
|
2018-10-22 19:52:11 +00:00
|
|
|
, connIdent = ConnIdent Nothing
|
2016-12-06 19:40:31 +00:00
|
|
|
}
|
|
|
|
|
2016-12-06 19:49:39 +00:00
|
|
|
closeConnection :: P2PConnection -> IO ()
|
|
|
|
closeConnection conn = do
|
2024-06-28 15:22:29 +00:00
|
|
|
closehandle (connIhdl conn)
|
|
|
|
closehandle (connOhdl conn)
|
|
|
|
where
|
|
|
|
closehandle (P2PHandle h) = hClose h
|
2024-07-26 19:25:15 +00:00
|
|
|
closehandle (P2PHandleTMVar _ _ closedv) =
|
|
|
|
atomically $ void $ tryPutTMVar closedv ()
|
2016-12-06 19:49:39 +00:00
|
|
|
|
2016-12-24 16:12:58 +00:00
|
|
|
-- Serves the protocol on a unix socket.
|
|
|
|
--
|
|
|
|
-- The callback is run to serve a connection, and is responsible for
|
|
|
|
-- closing the Handle when done.
|
|
|
|
--
|
|
|
|
-- Note that while the callback is running, other connections won't be
|
2016-12-24 16:49:28 +00:00
|
|
|
-- processed, so longterm work should be run in a separate thread by
|
2016-12-24 16:12:58 +00:00
|
|
|
-- the callback.
|
|
|
|
serveUnixSocket :: FilePath -> (Handle -> IO ()) -> IO ()
|
|
|
|
serveUnixSocket unixsocket serveconn = do
|
2020-11-24 16:38:12 +00:00
|
|
|
removeWhenExistsWith R.removeLink (toRawFilePath unixsocket)
|
2016-12-24 16:12:58 +00:00
|
|
|
soc <- S.socket S.AF_UNIX S.Stream S.defaultProtocol
|
|
|
|
S.bind soc (S.SockAddrUnix unixsocket)
|
|
|
|
-- Allow everyone to read and write to the socket,
|
|
|
|
-- so a daemon like tor, that is probably running as a different
|
|
|
|
-- de sock $ addModes
|
|
|
|
-- user, can access it.
|
|
|
|
--
|
|
|
|
-- Connections have to authenticate to do anything,
|
|
|
|
-- so it's fine that other local users can connect to the
|
|
|
|
-- socket.
|
2020-11-05 22:45:37 +00:00
|
|
|
modifyFileMode (toRawFilePath unixsocket) $ addModes
|
2016-12-24 16:12:58 +00:00
|
|
|
[groupReadMode, groupWriteMode, otherReadMode, otherWriteMode]
|
|
|
|
S.listen soc 2
|
|
|
|
forever $ do
|
|
|
|
(conn, _) <- S.accept soc
|
|
|
|
setupHandle conn >>= serveconn
|
|
|
|
|
2016-12-06 19:40:31 +00:00
|
|
|
setupHandle :: Socket -> IO Handle
|
|
|
|
setupHandle s = do
|
|
|
|
h <- socketToHandle s ReadWriteMode
|
|
|
|
hSetBuffering h LineBuffering
|
|
|
|
hSetBinaryMode h False
|
|
|
|
return h
|
|
|
|
|
2016-12-01 04:41:01 +00:00
|
|
|
-- Purposefully incomplete interpreter of Proto.
|
2016-12-01 03:54:00 +00:00
|
|
|
--
|
2016-12-01 04:41:01 +00:00
|
|
|
-- This only runs Net actions. No Local actions will be run
|
git-annex-shell: block relay requests
connRepo is only used when relaying git upload-pack and receive-pack.
That's only supposed to be used when git-annex-remotedaemon is serving
git-remote-tor-annex connections over tor. But, it was always set, and
so could be used in other places possibly.
Fixed by making connRepo optional in the P2P protocol interface.
In Command.EnableTor, it's not needed, because it only speaks the
protocol in order to check that it's able to connect back to itself via
the hidden service. So changed that to pass Nothing rather than the git
repo.
In Remote.Helper.Ssh, it's connecting to git-annex-shell p2pstdio,
so is making the requests, so will never need connRepo.
In git-annex-shell p2pstdio, it was accepting git upload-pack and
receive-pack requests over the P2P protocol, even though nothing sent
them. This is arguably a security hole, particularly if the user has
set environment variables like GIT_ANNEX_SHELL_LIMITED to prevent
git push/pull via git-annex-shell.
2024-06-10 17:53:28 +00:00
|
|
|
-- (those need the Annex monad).
|
2018-09-25 20:49:59 +00:00
|
|
|
runNetProto :: RunState -> P2PConnection -> Proto a -> IO (Either ProtoFailure a)
|
2018-03-12 19:19:40 +00:00
|
|
|
runNetProto runst conn = go
|
2016-11-20 16:08:16 +00:00
|
|
|
where
|
2016-12-01 04:41:01 +00:00
|
|
|
go :: RunProto IO
|
2016-12-10 15:12:18 +00:00
|
|
|
go (Pure v) = return (Right v)
|
2018-03-12 19:19:40 +00:00
|
|
|
go (Free (Net n)) = runNet runst conn go n
|
2018-09-25 20:49:59 +00:00
|
|
|
go (Free (Local _)) = return $ Left $
|
|
|
|
ProtoFailureMessage "unexpected annex operation attempted"
|
2016-11-20 16:08:16 +00:00
|
|
|
|
2016-12-02 17:45:45 +00:00
|
|
|
-- Interpreter of the Net part of Proto.
|
2016-12-01 04:41:01 +00:00
|
|
|
--
|
|
|
|
-- An interpreter of Proto has to be provided, to handle the rest of Proto
|
|
|
|
-- actions.
|
2018-09-25 20:49:59 +00:00
|
|
|
runNet :: (MonadIO m, MonadMask m) => RunState -> P2PConnection -> RunProto m -> NetF (Proto a) -> m (Either ProtoFailure a)
|
2018-03-12 19:19:40 +00:00
|
|
|
runNet runst conn runner f = case f of
|
2016-11-20 16:08:16 +00:00
|
|
|
SendMessage m next -> do
|
2024-06-28 15:22:29 +00:00
|
|
|
v <- liftIO $ do
|
2018-10-22 19:52:11 +00:00
|
|
|
debugMessage conn "P2P >" m
|
2024-06-28 15:22:29 +00:00
|
|
|
case connOhdl conn of
|
|
|
|
P2PHandle h -> tryNonAsync $ do
|
|
|
|
hPutStrLn h $ unwords (formatMessage m)
|
|
|
|
hFlush h
|
2024-07-26 19:25:15 +00:00
|
|
|
P2PHandleTMVar mv _ closedv -> tryNonAsync $
|
2024-07-22 19:48:46 +00:00
|
|
|
atomically $ putTMVar mv (Right m)
|
2024-07-26 19:25:15 +00:00
|
|
|
`orElse` readTMVar closedv
|
2016-11-22 01:22:58 +00:00
|
|
|
case v of
|
2018-09-25 20:49:59 +00:00
|
|
|
Left e -> return $ Left $ ProtoFailureException e
|
2016-11-22 01:22:58 +00:00
|
|
|
Right () -> runner next
|
2024-06-28 15:22:29 +00:00
|
|
|
ReceiveMessage next ->
|
|
|
|
let protoerr = return $ Left $
|
2024-07-11 11:46:52 +00:00
|
|
|
ProtoFailureMessage "protocol error"
|
2024-06-28 15:22:29 +00:00
|
|
|
gotmessage m = do
|
|
|
|
liftIO $ debugMessage conn "P2P <" m
|
|
|
|
runner (next (Just m))
|
|
|
|
in case connIhdl conn of
|
|
|
|
P2PHandle h -> do
|
|
|
|
v <- liftIO $ tryIOError $ getProtocolLine h
|
|
|
|
case v of
|
|
|
|
Left e -> return $ Left $ ProtoFailureIOError e
|
|
|
|
Right Nothing -> protoerr
|
|
|
|
Right (Just l) -> case parseMessage l of
|
|
|
|
Just m -> gotmessage m
|
|
|
|
Nothing -> runner (next Nothing)
|
2024-07-26 19:25:15 +00:00
|
|
|
P2PHandleTMVar mv _ closedv -> do
|
|
|
|
let recv = (Just <$> takeTMVar mv)
|
|
|
|
`orElse` (readTMVar closedv >> return Nothing)
|
|
|
|
liftIO (atomically recv) >>= \case
|
|
|
|
Just (Right m) -> gotmessage m
|
|
|
|
Just (Left _b) -> protoerr
|
|
|
|
Nothing -> runner (next Nothing)
|
2024-06-28 15:22:29 +00:00
|
|
|
SendBytes len b p next ->
|
|
|
|
case connOhdl conn of
|
|
|
|
P2PHandle h -> do
|
|
|
|
v <- liftIO $ tryNonAsync $ do
|
|
|
|
ok <- sendExactly len b h p
|
|
|
|
hFlush h
|
|
|
|
return ok
|
|
|
|
case v of
|
|
|
|
Right True -> runner next
|
|
|
|
Right False -> return $ Left $
|
|
|
|
ProtoFailureMessage "short data write"
|
|
|
|
Left e -> return $ Left $ ProtoFailureException e
|
2024-07-26 19:25:15 +00:00
|
|
|
P2PHandleTMVar mv waitv closedv -> do
|
2024-06-28 15:22:29 +00:00
|
|
|
liftIO $ atomically $ putTMVar mv (Left b)
|
2024-07-26 19:25:15 +00:00
|
|
|
`orElse` readTMVar closedv
|
2024-07-11 13:55:17 +00:00
|
|
|
-- Wait for the whole bytestring to
|
|
|
|
-- be processed.
|
2024-07-26 19:25:15 +00:00
|
|
|
case waitv of
|
|
|
|
Nothing -> noop
|
|
|
|
Just v -> liftIO $ atomically $
|
|
|
|
takeTMVar v
|
|
|
|
`orElse` readTMVar closedv
|
2024-06-28 15:22:29 +00:00
|
|
|
runner next
|
|
|
|
ReceiveBytes len p next ->
|
|
|
|
case connIhdl conn of
|
|
|
|
P2PHandle h -> do
|
|
|
|
v <- liftIO $ tryNonAsync $ receiveExactly len h p
|
|
|
|
case v of
|
|
|
|
Right b -> runner (next b)
|
|
|
|
Left e -> return $ Left $
|
|
|
|
ProtoFailureException e
|
2024-07-26 19:25:15 +00:00
|
|
|
P2PHandleTMVar mv _ closedv -> do
|
|
|
|
let recv = (Just <$> takeTMVar mv)
|
|
|
|
`orElse` (readTMVar closedv >> return Nothing)
|
|
|
|
liftIO (atomically recv) >>= \case
|
|
|
|
Just (Left b) -> runner (next b)
|
|
|
|
Just (Right _) -> return $ Left $
|
2024-07-11 11:46:52 +00:00
|
|
|
ProtoFailureMessage "protocol error"
|
2024-07-26 19:25:15 +00:00
|
|
|
Nothing -> return $ Left $
|
|
|
|
ProtoFailureMessage "connection closed"
|
2016-11-30 20:38:16 +00:00
|
|
|
CheckAuthToken _u t next -> do
|
2016-12-06 19:40:31 +00:00
|
|
|
let authed = connCheckAuth conn t
|
2016-11-20 20:42:18 +00:00
|
|
|
runner (next authed)
|
2016-11-22 01:22:58 +00:00
|
|
|
Relay hin hout next -> do
|
2016-12-01 04:27:07 +00:00
|
|
|
v <- liftIO $ runRelay runnerio hin hout
|
2016-11-22 01:22:58 +00:00
|
|
|
case v of
|
2018-09-25 20:49:59 +00:00
|
|
|
Left e -> return $ Left e
|
2016-12-08 19:47:49 +00:00
|
|
|
Right exitcode -> runner (next exitcode)
|
2016-11-22 01:22:58 +00:00
|
|
|
RelayService service next -> do
|
2016-12-06 19:40:31 +00:00
|
|
|
v <- liftIO $ runRelayService conn runnerio service
|
2016-11-22 01:22:58 +00:00
|
|
|
case v of
|
2018-09-25 20:49:59 +00:00
|
|
|
Left e -> return $ Left e
|
2016-12-08 19:47:49 +00:00
|
|
|
Right () -> runner next
|
2018-03-12 19:19:40 +00:00
|
|
|
SetProtocolVersion v next -> do
|
|
|
|
liftIO $ atomically $ writeTVar versiontvar v
|
|
|
|
runner next
|
|
|
|
GetProtocolVersion next ->
|
|
|
|
liftIO (readTVarIO versiontvar) >>= runner . next
|
2024-07-03 20:59:22 +00:00
|
|
|
GetMonotonicTimestamp next ->
|
2024-07-03 21:54:01 +00:00
|
|
|
liftIO currentMonotonicTimestamp >>= runner . next
|
2016-12-01 04:27:07 +00:00
|
|
|
where
|
|
|
|
-- This is only used for running Net actions when relaying,
|
2016-12-01 04:41:01 +00:00
|
|
|
-- so it's ok to use runNetProto, despite it not supporting
|
2016-12-01 04:27:07 +00:00
|
|
|
-- all Proto actions.
|
2018-03-12 19:19:40 +00:00
|
|
|
runnerio = runNetProto runst conn
|
|
|
|
versiontvar = case runst of
|
|
|
|
Serving _ _ tv -> tv
|
|
|
|
Client tv -> tv
|
2016-11-22 01:22:58 +00:00
|
|
|
|
2018-10-22 19:52:11 +00:00
|
|
|
debugMessage :: P2PConnection -> String -> Message -> IO ()
|
|
|
|
debugMessage conn prefix m = do
|
|
|
|
tid <- myThreadId
|
2021-04-05 17:40:31 +00:00
|
|
|
debug "P2P.IO" $ concat $ catMaybes $
|
2018-10-22 19:54:12 +00:00
|
|
|
[ (\ident -> "[" ++ ident ++ "] ") <$> mident
|
2018-10-22 19:52:11 +00:00
|
|
|
, Just $ "[" ++ show tid ++ "] "
|
|
|
|
, Just $ prefix ++ " " ++ unwords (formatMessage safem)
|
|
|
|
]
|
2016-12-09 20:55:48 +00:00
|
|
|
where
|
|
|
|
safem = case m of
|
|
|
|
AUTH u _ -> AUTH u nullAuthToken
|
|
|
|
_ -> m
|
2018-10-22 19:52:11 +00:00
|
|
|
ConnIdent mident = connIdent conn
|
2016-12-09 20:55:48 +00:00
|
|
|
|
2016-12-02 17:45:45 +00:00
|
|
|
-- Send exactly the specified number of bytes or returns False.
|
|
|
|
--
|
|
|
|
-- The ByteString can be larger or smaller than the specified length.
|
|
|
|
-- For example, it can be lazily streaming from a file that gets
|
|
|
|
-- appended to, or truncated.
|
|
|
|
--
|
|
|
|
-- Must avoid sending too many bytes as it would confuse the other end.
|
|
|
|
-- This is easily dealt with by truncating it.
|
|
|
|
--
|
2024-07-26 23:50:15 +00:00
|
|
|
-- However, the whole ByteString will be evaluated here, even if
|
|
|
|
-- the end of it does not get sent.
|
|
|
|
--
|
2016-12-02 17:45:45 +00:00
|
|
|
-- If too few bytes are sent, the only option is to give up on this
|
|
|
|
-- connection. False is returned to indicate this problem.
|
2016-12-07 17:37:35 +00:00
|
|
|
sendExactly :: Len -> L.ByteString -> Handle -> MeterUpdate -> IO Bool
|
2016-12-07 18:25:01 +00:00
|
|
|
sendExactly (Len n) b h p = do
|
2024-07-26 23:50:15 +00:00
|
|
|
let (x, y) = L.splitAt (fromIntegral n) b
|
|
|
|
sent <- meteredWrite' p (B.hPut h) x
|
|
|
|
L.length y `seq` return (fromBytesProcessed sent == n)
|
2016-12-07 18:25:01 +00:00
|
|
|
|
|
|
|
receiveExactly :: Len -> Handle -> MeterUpdate -> IO L.ByteString
|
|
|
|
receiveExactly (Len n) h p = hGetMetered h (Just n) p
|
2016-12-02 17:45:45 +00:00
|
|
|
|
2018-09-25 20:49:59 +00:00
|
|
|
runRelay :: RunProto IO -> RelayHandle -> RelayHandle -> IO (Either ProtoFailure ExitCode)
|
2016-12-08 19:47:49 +00:00
|
|
|
runRelay runner (RelayHandle hout) (RelayHandle hin) =
|
|
|
|
bracket setup cleanup go
|
2018-09-25 20:49:59 +00:00
|
|
|
`catchNonAsync` (return . Left . ProtoFailureException)
|
2016-11-20 16:08:16 +00:00
|
|
|
where
|
2016-11-21 23:24:55 +00:00
|
|
|
setup = do
|
|
|
|
v <- newEmptyMVar
|
2020-06-05 18:42:11 +00:00
|
|
|
t1 <- async $ relayFeeder runner v hin
|
|
|
|
t2 <- async $ relayReader v hout
|
|
|
|
return (v, t1, t2)
|
2016-11-20 16:08:16 +00:00
|
|
|
|
2020-06-05 18:42:11 +00:00
|
|
|
cleanup (_, t1, t2) = do
|
2016-11-21 23:24:55 +00:00
|
|
|
hClose hin
|
|
|
|
hClose hout
|
2020-06-05 18:42:11 +00:00
|
|
|
cancel t1
|
|
|
|
cancel t2
|
2016-11-21 23:24:55 +00:00
|
|
|
|
2020-06-05 18:42:11 +00:00
|
|
|
go (v, _, _) = relayHelper runner v
|
2016-11-20 16:08:16 +00:00
|
|
|
|
2018-09-25 20:49:59 +00:00
|
|
|
runRelayService :: P2PConnection -> RunProto IO -> Service -> IO (Either ProtoFailure ())
|
git-annex-shell: block relay requests
connRepo is only used when relaying git upload-pack and receive-pack.
That's only supposed to be used when git-annex-remotedaemon is serving
git-remote-tor-annex connections over tor. But, it was always set, and
so could be used in other places possibly.
Fixed by making connRepo optional in the P2P protocol interface.
In Command.EnableTor, it's not needed, because it only speaks the
protocol in order to check that it's able to connect back to itself via
the hidden service. So changed that to pass Nothing rather than the git
repo.
In Remote.Helper.Ssh, it's connecting to git-annex-shell p2pstdio,
so is making the requests, so will never need connRepo.
In git-annex-shell p2pstdio, it was accepting git upload-pack and
receive-pack requests over the P2P protocol, even though nothing sent
them. This is arguably a security hole, particularly if the user has
set environment variables like GIT_ANNEX_SHELL_LIMITED to prevent
git push/pull via git-annex-shell.
2024-06-10 17:53:28 +00:00
|
|
|
runRelayService conn runner service = case connRepo conn of
|
|
|
|
Just repo -> withCreateProcess (serviceproc' repo) go
|
2018-09-25 20:49:59 +00:00
|
|
|
`catchNonAsync` (return . Left . ProtoFailureException)
|
git-annex-shell: block relay requests
connRepo is only used when relaying git upload-pack and receive-pack.
That's only supposed to be used when git-annex-remotedaemon is serving
git-remote-tor-annex connections over tor. But, it was always set, and
so could be used in other places possibly.
Fixed by making connRepo optional in the P2P protocol interface.
In Command.EnableTor, it's not needed, because it only speaks the
protocol in order to check that it's able to connect back to itself via
the hidden service. So changed that to pass Nothing rather than the git
repo.
In Remote.Helper.Ssh, it's connecting to git-annex-shell p2pstdio,
so is making the requests, so will never need connRepo.
In git-annex-shell p2pstdio, it was accepting git upload-pack and
receive-pack requests over the P2P protocol, even though nothing sent
them. This is arguably a security hole, particularly if the user has
set environment variables like GIT_ANNEX_SHELL_LIMITED to prevent
git push/pull via git-annex-shell.
2024-06-10 17:53:28 +00:00
|
|
|
Nothing -> return $ Left $ ProtoFailureMessage
|
|
|
|
"relaying to git not supported on this connection"
|
2016-11-20 16:08:16 +00:00
|
|
|
where
|
|
|
|
cmd = case service of
|
|
|
|
UploadPack -> "upload-pack"
|
|
|
|
ReceivePack -> "receive-pack"
|
2016-11-21 21:27:38 +00:00
|
|
|
|
git-annex-shell: block relay requests
connRepo is only used when relaying git upload-pack and receive-pack.
That's only supposed to be used when git-annex-remotedaemon is serving
git-remote-tor-annex connections over tor. But, it was always set, and
so could be used in other places possibly.
Fixed by making connRepo optional in the P2P protocol interface.
In Command.EnableTor, it's not needed, because it only speaks the
protocol in order to check that it's able to connect back to itself via
the hidden service. So changed that to pass Nothing rather than the git
repo.
In Remote.Helper.Ssh, it's connecting to git-annex-shell p2pstdio,
so is making the requests, so will never need connRepo.
In git-annex-shell p2pstdio, it was accepting git upload-pack and
receive-pack requests over the P2P protocol, even though nothing sent
them. This is arguably a security hole, particularly if the user has
set environment variables like GIT_ANNEX_SHELL_LIMITED to prevent
git push/pull via git-annex-shell.
2024-06-10 17:53:28 +00:00
|
|
|
serviceproc repo = gitCreateProcess
|
2016-11-21 21:27:38 +00:00
|
|
|
[ Param cmd
|
git-annex-shell: block relay requests
connRepo is only used when relaying git upload-pack and receive-pack.
That's only supposed to be used when git-annex-remotedaemon is serving
git-remote-tor-annex connections over tor. But, it was always set, and
so could be used in other places possibly.
Fixed by making connRepo optional in the P2P protocol interface.
In Command.EnableTor, it's not needed, because it only speaks the
protocol in order to check that it's able to connect back to itself via
the hidden service. So changed that to pass Nothing rather than the git
repo.
In Remote.Helper.Ssh, it's connecting to git-annex-shell p2pstdio,
so is making the requests, so will never need connRepo.
In git-annex-shell p2pstdio, it was accepting git upload-pack and
receive-pack requests over the P2P protocol, even though nothing sent
them. This is arguably a security hole, particularly if the user has
set environment variables like GIT_ANNEX_SHELL_LIMITED to prevent
git push/pull via git-annex-shell.
2024-06-10 17:53:28 +00:00
|
|
|
, File (fromRawFilePath (repoPath repo))
|
|
|
|
] repo
|
|
|
|
serviceproc' repo = (serviceproc repo)
|
2020-06-03 17:47:28 +00:00
|
|
|
{ std_out = CreatePipe
|
|
|
|
, std_in = CreatePipe
|
|
|
|
}
|
2016-11-21 21:27:38 +00:00
|
|
|
|
2020-06-03 17:47:28 +00:00
|
|
|
go (Just hin) (Just hout) _ pid = do
|
2016-11-21 23:24:55 +00:00
|
|
|
v <- newEmptyMVar
|
2020-06-03 17:47:28 +00:00
|
|
|
r <- withAsync (relayFeeder runner v hin) $ \_ ->
|
|
|
|
withAsync (relayReader v hout) $ \_ ->
|
|
|
|
withAsync (waitexit v pid) $ \_ -> do
|
|
|
|
r <- runrelay v
|
|
|
|
hClose hin
|
|
|
|
hClose hout
|
|
|
|
return r
|
2016-11-21 21:27:38 +00:00
|
|
|
void $ waitForProcess pid
|
2020-06-03 17:47:28 +00:00
|
|
|
return r
|
|
|
|
go _ _ _ _ = error "internal"
|
2016-11-21 23:24:55 +00:00
|
|
|
|
2020-06-03 17:47:28 +00:00
|
|
|
runrelay v = relayHelper runner v >>= \case
|
|
|
|
Left e -> return $ Left e
|
|
|
|
Right exitcode -> runner $
|
|
|
|
net $ relayToPeer (RelayDone exitcode)
|
|
|
|
|
2016-11-21 23:24:55 +00:00
|
|
|
waitexit v pid = putMVar v . RelayDone =<< waitForProcess pid
|
2016-11-20 16:08:16 +00:00
|
|
|
|
2016-11-21 23:24:55 +00:00
|
|
|
-- Processes RelayData as it is put into the MVar.
|
2018-09-25 20:49:59 +00:00
|
|
|
relayHelper :: RunProto IO -> MVar RelayData -> IO (Either ProtoFailure ExitCode)
|
2016-12-08 19:15:29 +00:00
|
|
|
relayHelper runner v = loop
|
2016-11-21 23:24:55 +00:00
|
|
|
where
|
|
|
|
loop = do
|
2016-11-20 16:08:16 +00:00
|
|
|
d <- takeMVar v
|
|
|
|
case d of
|
2016-11-21 23:24:55 +00:00
|
|
|
RelayToPeer b -> do
|
2016-11-22 01:22:58 +00:00
|
|
|
r <- runner $ net $ relayToPeer (RelayToPeer b)
|
|
|
|
case r of
|
2016-12-08 19:47:49 +00:00
|
|
|
Left e -> return (Left e)
|
|
|
|
Right () -> loop
|
2016-11-21 23:24:55 +00:00
|
|
|
RelayDone exitcode -> do
|
2016-11-22 01:22:58 +00:00
|
|
|
_ <- runner $ net $ relayToPeer (RelayDone exitcode)
|
2016-12-08 19:47:49 +00:00
|
|
|
return (Right exitcode)
|
2016-12-08 19:15:29 +00:00
|
|
|
RelayFromPeer _ -> loop -- not handled here
|
2016-11-21 23:24:55 +00:00
|
|
|
|
2016-12-08 19:15:29 +00:00
|
|
|
-- Takes input from the peer, and sends it to the relay process's stdin.
|
2016-11-22 01:45:56 +00:00
|
|
|
-- Repeats until the peer tells it it's done or hangs up.
|
2016-12-08 19:15:29 +00:00
|
|
|
relayFeeder :: RunProto IO -> MVar RelayData -> Handle -> IO ()
|
|
|
|
relayFeeder runner v hin = loop
|
2016-11-21 23:24:55 +00:00
|
|
|
where
|
|
|
|
loop = do
|
2016-11-22 01:22:58 +00:00
|
|
|
mrd <- runner $ net relayFromPeer
|
|
|
|
case mrd of
|
2016-12-08 19:47:49 +00:00
|
|
|
Left _e ->
|
2016-12-08 19:15:29 +00:00
|
|
|
putMVar v (RelayDone (ExitFailure 1))
|
2016-12-08 19:47:49 +00:00
|
|
|
Right (RelayDone exitcode) ->
|
2016-12-08 19:15:29 +00:00
|
|
|
putMVar v (RelayDone exitcode)
|
2016-12-08 19:47:49 +00:00
|
|
|
Right (RelayFromPeer b) -> do
|
2016-12-08 19:15:29 +00:00
|
|
|
L.hPut hin b
|
|
|
|
hFlush hin
|
|
|
|
loop
|
2016-12-08 19:47:49 +00:00
|
|
|
Right (RelayToPeer _) -> loop -- not handled here
|
2016-11-21 23:24:55 +00:00
|
|
|
|
|
|
|
-- Reads input from the Handle and puts it into the MVar for relaying to
|
|
|
|
-- the peer. Continues until EOF on the Handle.
|
|
|
|
relayReader :: MVar RelayData -> Handle -> IO ()
|
|
|
|
relayReader v hout = loop
|
|
|
|
where
|
|
|
|
loop = do
|
2016-11-22 00:56:58 +00:00
|
|
|
bs <- getsome []
|
|
|
|
case bs of
|
|
|
|
[] -> return ()
|
|
|
|
_ -> do
|
|
|
|
putMVar v $ RelayToPeer (L.fromChunks bs)
|
2016-11-21 23:24:55 +00:00
|
|
|
loop
|
2016-11-22 00:56:58 +00:00
|
|
|
|
2019-03-27 15:15:20 +00:00
|
|
|
-- Wait for the first available chunk. Then, without blocking,
|
2016-11-22 00:56:58 +00:00
|
|
|
-- try to get more chunks, in case a stream of chunks is being
|
|
|
|
-- written in close succession.
|
|
|
|
--
|
|
|
|
-- On Windows, hGetNonBlocking is broken, so avoid using it there.
|
|
|
|
getsome [] = do
|
|
|
|
b <- B.hGetSome hout chunk
|
|
|
|
if B.null b
|
|
|
|
then return []
|
|
|
|
#ifndef mingw32_HOST_OS
|
|
|
|
else getsome [b]
|
|
|
|
#else
|
|
|
|
else return [b]
|
|
|
|
#endif
|
|
|
|
getsome bs = do
|
|
|
|
b <- B.hGetNonBlocking hout chunk
|
|
|
|
if B.null b
|
|
|
|
then return (reverse bs)
|
|
|
|
else getsome (b:bs)
|
|
|
|
|
|
|
|
chunk = 65536
|