aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--CHANGELOG2
-rw-r--r--Command/EnableTor.hs36
-rw-r--r--P2P/IO.hs29
-rw-r--r--RemoteDaemon/Transport/Tor.hs16
-rw-r--r--doc/bugs/YouTube_-_error_in_importfeed.mdwn3
-rw-r--r--doc/todo/tor.mdwn1
6 files changed, 67 insertions, 20 deletions
diff --git a/CHANGELOG b/CHANGELOG
index 220aeea41..2d7ea22a7 100644
--- a/CHANGELOG
+++ b/CHANGELOG
@@ -22,6 +22,8 @@ git-annex (6.20161211) UNRELEASED; urgency=medium
* enable-tor: Put tor sockets in /var/lib/tor-annex/, rather
than in /etc/tor/hidden_service/.
* enable-tor: No longer needs to be run as root.
+ * enable-tor: When run as a regular user, test a connection back to
+ the hidden service over tor.
* Fix build with directory-1.3.
* Debian: Suggest tor and magic-wormhole.
* Debian: Build webapp on armel.
diff --git a/Command/EnableTor.hs b/Command/EnableTor.hs
index c81968a55..2b7d62635 100644
--- a/Command/EnableTor.hs
+++ b/Command/EnableTor.hs
@@ -10,18 +10,19 @@
module Command.EnableTor where
import Command
+import qualified Annex
import P2P.Address
import Utility.Tor
import Annex.UUID
import Config.Files
+import P2P.IO
+import Utility.ThreadScheduler
#ifndef mingw32_HOST_OS
import Utility.Su
import System.Posix.User
#endif
--- This runs as root, so avoid making any commits or initializing
--- git-annex, or doing other things that create root-owned files.
cmd :: Command
cmd = noCommit $ dontCheck repoExists $
command "enable-tor" SectionSetup "enable tor hidden service"
@@ -30,6 +31,8 @@ cmd = noCommit $ dontCheck repoExists $
seek :: CmdParams -> CommandSeek
seek = withWords start
+-- This runs as root, so avoid making any commits or initializing
+-- git-annex, or doing other things that create root-owned files.
start :: [String] -> CommandStart
start os = do
uuid <- getUUID
@@ -42,11 +45,12 @@ start os = do
Nothing -> giveup "Need user-id parameter."
Just userid -> go uuid userid
else do
- liftIO $ putStrLn "Need root access to enable tor..."
+ showStart "enable-tor" ""
+ showLongNote "Need root access to enable tor..."
gitannex <- liftIO readProgramFile
let ps = [Param (cmdname cmd), Param (show curruserid)]
ifM (liftIO $ runAsRoot gitannex ps)
- ( stop
+ ( next $ next checkHiddenService
, giveup $ unwords $
[ "Failed to run as root:" , gitannex ] ++ toCommand ps
)
@@ -59,3 +63,27 @@ start os = do
addHiddenService torAppName userid (fromUUID uuid)
storeP2PAddress $ TorAnnex onionaddr onionport
stop
+
+checkHiddenService :: CommandCleanup
+checkHiddenService = do
+ showLongNote "Tor hidden service is configured. Checking connection to it. This may take a few minutes."
+ go (150 :: Int) =<< filter istoraddr <$> loadP2PAddresses
+ where
+ istoraddr (TorAnnex _ _) = True
+
+ go 0 _ = giveup "Still unable to connect to hidden service. It might not yet be usable by others. Please check Tor's logs for details."
+ go _ [] = giveup "Somehow didn't get an onion address."
+ go n addrs@(addr:_) = do
+ g <- Annex.gitRepo
+ -- Connect to ourselves; don't bother trying to auth,
+ -- we just want to know if the circuit works.
+ cv <- liftIO $ tryNonAsync $ connectPeer g addr
+ case cv of
+ Left e -> do
+ warning $ "Unable to connect to hidden service. It may not yet have propigated to the Tor network. (" ++ show e ++ ") Will retry.."
+ liftIO $ threadDelaySeconds (Seconds 2)
+ go (n-1) addrs
+ Right conn -> do
+ liftIO $ closeConnection conn
+ showLongNote "Tor hidden service is working."
+ return True
diff --git a/P2P/IO.hs b/P2P/IO.hs
index 3e0999775..49f28bff1 100644
--- a/P2P/IO.hs
+++ b/P2P/IO.hs
@@ -68,6 +68,35 @@ closeConnection conn = do
hClose (connIhdl conn)
hClose (connOhdl conn)
+-- 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
+-- processes, so longterm work should be run in a separate thread by
+-- the callback.
+serveUnixSocket :: FilePath -> (Handle -> IO ()) -> IO ()
+serveUnixSocket unixsocket serveconn = do
+ nukeFile unixsocket
+ 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.
+ modifyFileMode unixsocket $ addModes
+ [groupReadMode, groupWriteMode, otherReadMode, otherWriteMode]
+ S.listen soc 2
+ forever $ do
+ (conn, _) <- S.accept soc
+ h <- setupHandle conn
+ serveconn conn
+
setupHandle :: Socket -> IO Handle
setupHandle s = do
h <- socketToHandle s ReadWriteMode
diff --git a/RemoteDaemon/Transport/Tor.hs b/RemoteDaemon/Transport/Tor.hs
index 0fbe9a720..43ff3a2c1 100644
--- a/RemoteDaemon/Transport/Tor.hs
+++ b/RemoteDaemon/Transport/Tor.hs
@@ -48,22 +48,8 @@ server th@(TransportHandle (LocalRepo r) _) = do
replicateM_ maxConnections $
forkIO $ forever $ serveClient th u r q
- nukeFile sock
- soc <- S.socket S.AF_UNIX S.Stream S.defaultProtocol
- S.bind soc (S.SockAddrUnix sock)
- -- Allow everyone to read and write to the socket; tor
- -- is probably running as a different user.
- -- Connections have to authenticate to do anything,
- -- so it's fine that other local users can connect to the
- -- socket.
- modifyFileMode sock $ addModes
- [groupReadMode, groupWriteMode, otherReadMode, otherWriteMode]
-
- S.listen soc 2
debugM "remotedaemon" "Tor hidden service running"
- forever $ do
- (conn, _) <- S.accept soc
- h <- setupHandle conn
+ serveUnixSocket sock $ \conn -> do
ok <- atomically $ ifM (isFullTBMQueue q)
( return False
, do
diff --git a/doc/bugs/YouTube_-_error_in_importfeed.mdwn b/doc/bugs/YouTube_-_error_in_importfeed.mdwn
index b02348f65..d300c621f 100644
--- a/doc/bugs/YouTube_-_error_in_importfeed.mdwn
+++ b/doc/bugs/YouTube_-_error_in_importfeed.mdwn
@@ -69,3 +69,6 @@ ok
### Have you had any luck using git-annex before? (Sometimes we get tired of reading bug reports all day and a lil' positive end note does wonders)
Yes, for years. I donated to fund the dev and proudly display my git-annex stickers!
+
+> This is now fixed in feed's git repository, and will be in the next
+> release of feed after the current 0.3.11.1 release. [[done]] --[[Joey]]
diff --git a/doc/todo/tor.mdwn b/doc/todo/tor.mdwn
index f0c193677..cb0bc4d41 100644
--- a/doc/todo/tor.mdwn
+++ b/doc/todo/tor.mdwn
@@ -4,7 +4,6 @@ Mostly working!
Current todo list:
-* Make enable-tor check connection back to itself to verify tor is working.
* When a transfer can't be done because another transfer of the same
object is already in progress, the message about this is output by the
remotedaemon --debug, but not forwarded to the peer, which shows