2016-11-30 18:35:24 +00:00
{- git - annex command
-
- Copyright 2016 Joey Hess < id @ joeyh . name >
-
- Licensed under the GNU GPL version 3 or higher .
- }
module Command.P2P where
import Command
import P2P.Address
import P2P.Auth
2016-12-16 22:26:07 +00:00
import P2P.IO
import qualified P2P.Protocol as P2P
2016-11-30 19:14:54 +00:00
import Git.Types
import qualified Git.Remote
2016-12-16 22:26:07 +00:00
import qualified Git.Command
import qualified Annex
import Annex.UUID
import Config
2016-12-18 20:50:58 +00:00
import Utility.AuthToken
2017-12-31 20:08:31 +00:00
import Utility.Tmp.Dir
2016-12-18 20:50:58 +00:00
import Utility.FileMode
import Utility.ThreadScheduler
import qualified Utility.MagicWormhole as Wormhole
import Control.Concurrent.Async
import qualified Data.Text as T
2017-02-03 19:06:17 +00:00
import Data.Time.Clock.POSIX
2016-11-30 18:35:24 +00:00
cmd :: Command
cmd = command " p2p " SectionSetup
" configure peer-2-peer links between repositories "
paramNothing ( seek <$$> optParser )
data P2POpts
= GenAddresses
2016-12-16 19:36:59 +00:00
| LinkRemote
2016-12-18 20:50:58 +00:00
| Pair
2016-11-30 18:35:24 +00:00
2016-12-16 22:26:07 +00:00
optParser :: CmdParamsDesc -> Parser ( P2POpts , Maybe RemoteName )
optParser _ = ( , )
2016-12-18 20:50:58 +00:00
<$> ( pair <|> linkremote <|> genaddresses )
2016-12-16 19:36:59 +00:00
<*> optional name
2016-11-30 18:35:24 +00:00
where
genaddresses = flag' GenAddresses
( long " gen-addresses "
<> help " generate addresses that allow accessing this repository over P2P networks "
)
2016-12-16 19:36:59 +00:00
linkremote = flag' LinkRemote
2016-11-30 19:14:54 +00:00
( long " link "
2016-12-16 19:36:59 +00:00
<> help " set up a P2P link to a git remote "
)
2016-12-18 20:50:58 +00:00
pair = flag' Pair
( long " pair "
<> help " pair with another repository "
)
name = Git . Remote . makeLegalName <$> strOption
2016-12-16 19:36:59 +00:00
( long " name "
<> metavar paramName
<> help " name of remote "
2016-11-30 19:14:54 +00:00
)
2016-11-30 18:35:24 +00:00
2016-12-16 22:26:07 +00:00
seek :: ( P2POpts , Maybe RemoteName ) -> CommandSeek
seek ( GenAddresses , _ ) = genAddresses =<< loadP2PAddresses
seek ( LinkRemote , Just name ) = commandAction $
2016-12-18 20:50:58 +00:00
linkRemote name
2016-12-16 22:26:07 +00:00
seek ( LinkRemote , Nothing ) = commandAction $
linkRemote =<< unusedPeerRemoteName
2016-12-18 20:50:58 +00:00
seek ( Pair , Just name ) = commandAction $
2016-12-18 21:01:15 +00:00
startPairing name =<< loadP2PAddresses
2016-12-18 20:50:58 +00:00
seek ( Pair , Nothing ) = commandAction $ do
name <- unusedPeerRemoteName
2016-12-18 21:01:15 +00:00
startPairing name =<< loadP2PAddresses
2016-12-16 22:26:07 +00:00
unusedPeerRemoteName :: Annex RemoteName
unusedPeerRemoteName = go ( 1 :: Integer ) =<< usednames
where
2018-01-09 19:36:56 +00:00
usednames = mapMaybe remoteName <$> Annex . getGitRemotes
2016-12-16 22:26:07 +00:00
go n names = do
let name = " peer " ++ show n
if name ` elem ` names
then go ( n + 1 ) names
else return name
2016-12-16 19:36:59 +00:00
2016-11-30 19:14:54 +00:00
-- Only addresses are output to stdout, to allow scripting.
genAddresses :: [ P2PAddress ] -> Annex ()
genAddresses [] = giveup " No P2P networks are currrently available. "
genAddresses addrs = do
authtoken <- liftIO $ genAuthToken 128
storeP2PAuthToken authtoken
earlyWarning " These addresses allow access to this git-annex repository. Only share them with people you trust with that access, using trusted communication channels! "
liftIO $ putStr $ unlines $
map formatP2PAddress $
map ( ` P2PAddressAuth ` authtoken ) addrs
-- Address is read from stdin, to avoid leaking it in shell history.
2016-12-16 22:26:07 +00:00
linkRemote :: RemoteName -> CommandStart
linkRemote remotename = do
2017-11-28 18:40:26 +00:00
showStart' " p2p link " ( Just remotename )
2017-05-11 22:31:14 +00:00
next $ next promptaddr
2016-11-30 19:14:54 +00:00
where
2017-05-11 22:31:14 +00:00
promptaddr = do
2016-11-30 19:14:54 +00:00
liftIO $ putStrLn " "
2016-12-07 16:38:21 +00:00
liftIO $ putStr " Enter peer address: "
2016-11-30 19:14:54 +00:00
liftIO $ hFlush stdout
s <- liftIO getLine
if null s
then do
liftIO $ hPutStrLn stderr " Nothing entered, giving up. "
return False
else case unformatP2PAddress s of
Nothing -> do
liftIO $ hPutStrLn stderr " Unable to parse that address, please check its format and try again. "
2017-05-11 22:31:14 +00:00
promptaddr
2016-12-18 20:50:58 +00:00
Just addr -> do
r <- setupLink remotename addr
case r of
LinkSuccess -> return True
ConnectionError e -> giveup e
AuthenticationError e -> giveup e
2016-12-18 21:01:15 +00:00
startPairing :: RemoteName -> [ P2PAddress ] -> CommandStart
startPairing _ [] = giveup " No P2P networks are currrently available. "
startPairing remotename addrs = do
2017-11-28 18:40:26 +00:00
showStart' " p2p pair " ( Just remotename )
2016-12-18 21:01:15 +00:00
ifM ( liftIO Wormhole . isInstalled )
( next $ performPairing remotename addrs
, giveup " Magic Wormhole is not installed, and is needed for pairing. Install it from your distribution or from https://github.com/warner/magic-wormhole/ "
)
performPairing :: RemoteName -> [ P2PAddress ] -> CommandPerform
performPairing remotename addrs = do
-- This note is displayed mainly so when magic wormhole
-- complains about possible protocol mismatches or other problems,
-- it's clear what's doing the complaining.
2016-12-18 21:31:02 +00:00
showNote " using Magic Wormhole "
2016-12-18 21:01:15 +00:00
next $ do
showOutput
2016-12-18 20:50:58 +00:00
r <- wormholePairing remotename addrs ui
case r of
PairSuccess -> return True
SendFailed -> do
warning " Failed sending data to pair. "
return False
ReceiveFailed -> do
warning " Failed receiving data from pair. "
return False
LinkFailed e -> do
warning $ " Failed linking to pair: " ++ e
return False
where
ui observer producer = do
ourcode <- Wormhole . waitCode observer
putStrLn " "
putStrLn $ " This repository's pairing code is: " ++
Wormhole . fromCode ourcode
putStrLn " "
theircode <- getcode ourcode
Wormhole . sendCode producer theircode
getcode ourcode = do
putStr " Enter the other repository's pairing code: "
hFlush stdout
l <- getLine
case Wormhole . toCode l of
Just code
2016-12-18 21:01:15 +00:00
| code /= ourcode -> do
2016-12-18 21:13:06 +00:00
putStrLn " Exchanging pairing data... "
2016-12-18 21:01:15 +00:00
return code
2016-12-18 20:50:58 +00:00
| otherwise -> do
2016-12-27 20:36:05 +00:00
putStrLn " Oops -- You entered this repository's pairing code. Enter the pairing code of the *other* repository. "
2016-12-18 20:50:58 +00:00
getcode ourcode
Nothing -> do
2016-12-24 20:56:56 +00:00
putStrLn " That does not look like a valiad pairing code. Try again... "
2016-12-18 20:50:58 +00:00
getcode ourcode
-- We generate half of the authtoken; the pair will provide
-- the other half.
newtype HalfAuthToken = HalfAuthToken T . Text
deriving ( Show )
data PairData = PairData HalfAuthToken [ P2PAddress ]
deriving ( Show )
serializePairData :: PairData -> String
serializePairData ( PairData ( HalfAuthToken ha ) addrs ) = unlines $
T . unpack ha : map formatP2PAddress addrs
deserializePairData :: String -> Maybe PairData
deserializePairData s = case lines s of
[] -> Nothing
( ha : l ) -> do
addrs <- mapM unformatP2PAddress l
return ( PairData ( HalfAuthToken ( T . pack ha ) ) addrs )
data PairingResult
= PairSuccess
| SendFailed
| ReceiveFailed
| LinkFailed String
wormholePairing
:: RemoteName
-> [ P2PAddress ]
-> ( Wormhole . CodeObserver -> Wormhole . CodeProducer -> IO () )
-> Annex PairingResult
wormholePairing remotename ouraddrs ui = do
ourhalf <- liftIO $ HalfAuthToken . fromAuthToken
<$> genAuthToken 64
let ourpairdata = PairData ourhalf ouraddrs
-- The magic wormhole interface only supports exchanging
-- files. Permissions of received files may allow others
-- to read them. So, set up a temp directory that only
-- we can read.
withTmpDir " pair " $ \ tmp -> do
liftIO $ void $ tryIO $ modifyFileMode tmp $
removeModes otherGroupModes
let sendf = tmp </> " send "
let recvf = tmp </> " recv "
liftIO $ writeFileProtected sendf $
serializePairData ourpairdata
observer <- liftIO Wormhole . mkCodeObserver
producer <- liftIO Wormhole . mkCodeProducer
void $ liftIO $ async $ ui observer producer
2017-02-03 19:06:17 +00:00
-- Provide an appid to magic wormhole, to avoid using
-- the same channels that other wormhole users use.
--
-- Since a version of git-annex that did not provide an
-- appid is shipping in Debian 9, and having one side
-- provide an appid while the other does not will make
-- wormhole fail, this is deferred until 2021-12-31.
-- After that point, all git-annex's should have been
-- upgraded to include this code, and they will start
-- providing an appid.
--
-- This assumes reasonably good client clocks. If the clock
-- is completely wrong, it won't use the appid at that
-- point, and pairing will fail. On 2021-12-31, minor clock
-- skew may also cause transient problems.
--
-- After 2021-12-31, this can be changed to simply
-- always provide the appid.
now <- liftIO getPOSIXTime
let wormholeparams = if now < 1640950000
then []
else Wormhole . appId " git-annex.branchable.com/p2p-setup "
2016-12-18 20:50:58 +00:00
( sendres , recvres ) <- liftIO $
2017-02-03 19:06:17 +00:00
Wormhole . sendFile sendf observer wormholeparams
2016-12-18 20:50:58 +00:00
` concurrently `
2017-02-03 19:06:17 +00:00
Wormhole . receiveFile recvf producer wormholeparams
2016-12-18 20:50:58 +00:00
liftIO $ nukeFile sendf
if sendres /= True
then return SendFailed
else if recvres /= True
then return ReceiveFailed
else do
r <- liftIO $ tryIO $
2016-12-24 18:46:31 +00:00
readFileStrict recvf
2016-12-18 20:50:58 +00:00
case r of
Left _e -> return ReceiveFailed
Right s -> maybe
( return ReceiveFailed )
( finishPairing 100 remotename ourhalf )
( deserializePairData s )
-- | Allow the peer we're pairing with to authenticate to us,
-- using an authtoken constructed from the two HalfAuthTokens.
-- Connect to the peer we're pairing with, and try to link to them.
--
-- Multiple addresses may have been received for the peer. This only
-- makes a link to one address.
--
-- Since we're racing the peer as they do the same, the first try is likely
-- to fail to authenticate. Can retry any number of times, to avoid the
-- users needing to redo the whole process.
finishPairing :: Int -> RemoteName -> HalfAuthToken -> PairData -> Annex PairingResult
finishPairing retries remotename ( HalfAuthToken ourhalf ) ( PairData ( HalfAuthToken theirhalf ) theiraddrs ) = do
case ( toAuthToken ( ourhalf <> theirhalf ) , toAuthToken ( theirhalf <> ourhalf ) ) of
( Just ourauthtoken , Just theirauthtoken ) -> do
2016-12-18 21:13:06 +00:00
liftIO $ putStrLn $ " Successfully exchanged pairing data. Connecting to " ++ remotename ++ " ... "
2016-12-18 20:50:58 +00:00
storeP2PAuthToken ourauthtoken
go retries theiraddrs theirauthtoken
_ -> return ReceiveFailed
where
go 0 [] _ = return $ LinkFailed $ " Unable to connect to " ++ remotename ++ " . "
go n [] theirauthtoken = do
liftIO $ threadDelaySeconds ( Seconds 2 )
liftIO $ putStrLn $ " Unable to connect to " ++ remotename ++ " . Retrying... "
go ( n - 1 ) theiraddrs theirauthtoken
go n ( addr : rest ) theirauthtoken = do
r <- setupLink remotename ( P2PAddressAuth addr theirauthtoken )
case r of
LinkSuccess -> return PairSuccess
_ -> go n rest theirauthtoken
data LinkResult
= LinkSuccess
| ConnectionError String
| AuthenticationError String
setupLink :: RemoteName -> P2PAddressAuth -> Annex LinkResult
setupLink remotename ( P2PAddressAuth addr authtoken ) = do
g <- Annex . gitRepo
cv <- liftIO $ tryNonAsync $ connectPeer g addr
case cv of
Left e -> return $ ConnectionError $ " Unable to connect with peer. Please check that the peer is connected to the network, and try again. ( " ++ show e ++ " ) "
Right conn -> do
u <- getUUID
2018-03-12 17:43:19 +00:00
let proto = P2P . auth u authtoken noop
2018-03-12 19:19:40 +00:00
runst <- liftIO $ mkRunState Client
go =<< liftIO ( runNetProto runst conn proto )
2016-12-18 20:50:58 +00:00
where
go ( Right ( Just theiruuid ) ) = do
ok <- inRepo $ Git . Command . runBool
[ Param " remote " , Param " add "
, Param remotename
, Param ( formatP2PAddress addr )
]
when ok $ do
storeUUIDIn ( remoteConfig remotename " uuid " ) theiruuid
storeP2PRemoteAuthToken addr authtoken
return LinkSuccess
go ( Right Nothing ) = return $ AuthenticationError " Unable to authenticate with peer. Please check the address and try again. "
2018-09-25 20:49:59 +00:00
go ( Left e ) = return $ AuthenticationError $ " Unable to authenticate with peer: " ++ describeProtoFailure e