aboutsummaryrefslogtreecommitdiff
path: root/CmdLine
diff options
context:
space:
mode:
authorGravatar Joey Hess <joeyh@joeyh.name>2016-11-21 17:27:38 -0400
committerGravatar Joey Hess <joeyh@joeyh.name>2016-11-21 17:27:38 -0400
commit01bf227ad1d9bd30d6fad2dc104b264a1f55c2c4 (patch)
treef893d0e14aea0cdec4dbe04d4c4703c44be658ac /CmdLine
parent849256634ad1234f9957532e0131e0e2b491bdeb (diff)
Added git-remote-tor-annex, which allows git pull and push to the tor hidden service.
Almost working, but there's a bug in the relaying. Also, made tor hidden service setup pick a random port, to make it harder to port scan. This commit was sponsored by Boyd Stephen Smith Jr. on Patreon.
Diffstat (limited to 'CmdLine')
-rw-r--r--CmdLine/GitRemoteTorAnnex.hs62
1 files changed, 62 insertions, 0 deletions
diff --git a/CmdLine/GitRemoteTorAnnex.hs b/CmdLine/GitRemoteTorAnnex.hs
new file mode 100644
index 000000000..bc001f42f
--- /dev/null
+++ b/CmdLine/GitRemoteTorAnnex.hs
@@ -0,0 +1,62 @@
+{- git-remote-tor-annex program
+ -
+ - Copyright 2016 Joey Hess <id@joeyh.name>
+ -
+ - Licensed under the GNU GPL version 3 or higher.
+ -}
+
+module CmdLine.GitRemoteTorAnnex where
+
+import Common
+import qualified Annex
+import qualified Git.CurrentRepo
+import Remote.Helper.P2P
+import Remote.Helper.P2P.IO
+import Remote.Helper.Tor
+import Utility.Tor
+import Annex.UUID
+
+run :: [String] -> IO ()
+run (_remotename:address:[]) = forever $ do
+ -- gitremote-helpers protocol
+ l <- getLine
+ case l of
+ "capabilities" -> do
+ putStrLn "connect"
+ putStrLn ""
+ "connect git-upload-pack" -> go UploadPack
+ "connect git-receive-pack" -> go ReceivePack
+ _ -> error $ "git-remote-helpers protocol error at " ++ show l
+ where
+ (onionaddress, onionport)
+ | '/' `elem` address = parseAddressPort $
+ reverse $ takeWhile (/= '/') $ reverse address
+ | otherwise = parseAddressPort address
+ go service = do
+ putStrLn ""
+ hFlush stdout
+ connectService onionaddress onionport service >>= exitWith
+run (_remotename:[]) = giveup "remote address not configured"
+run _ = giveup "expected remote name and address parameters"
+
+parseAddressPort :: String -> (OnionAddress, OnionPort)
+parseAddressPort s =
+ let (a, sp) = separate (== ':') s
+ in case readish sp of
+ Nothing -> giveup "onion address must include port number"
+ Just p -> (OnionAddress a, p)
+
+connectService :: OnionAddress -> OnionPort -> Service -> IO ExitCode
+connectService address port service = do
+ state <- Annex.new =<< Git.CurrentRepo.get
+ Annex.eval state $ do
+ authtoken <- fromMaybe nullAuthToken
+ <$> getTorAuthToken address
+ myuuid <- getUUID
+ g <- Annex.gitRepo
+ h <- liftIO $ torHandle =<< connectHiddenService address port
+ runNetProtoHandle h h g $ do
+ v <- auth myuuid authtoken
+ case v of
+ Just _theiruuid -> connect service stdin stdout
+ Nothing -> giveup $ "authentication failed, perhaps you need to set " ++ torAuthTokenEnv