This commit is contained in:
Joey Hess 2016-12-22 13:59:21 -04:00
parent 942ea305a2
commit 3aaabc906b
No known key found for this signature in database
GPG key ID: C910D9222512E3C7
6 changed files with 67 additions and 20 deletions

View file

@ -22,6 +22,8 @@ git-annex (6.20161211) UNRELEASED; urgency=medium
* enable-tor: Put tor sockets in /var/lib/tor-annex/, rather * enable-tor: Put tor sockets in /var/lib/tor-annex/, rather
than in /etc/tor/hidden_service/. than in /etc/tor/hidden_service/.
* enable-tor: No longer needs to be run as root. * 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. * Fix build with directory-1.3.
* Debian: Suggest tor and magic-wormhole. * Debian: Suggest tor and magic-wormhole.
* Debian: Build webapp on armel. * Debian: Build webapp on armel.

View file

@ -10,18 +10,19 @@
module Command.EnableTor where module Command.EnableTor where
import Command import Command
import qualified Annex
import P2P.Address import P2P.Address
import Utility.Tor import Utility.Tor
import Annex.UUID import Annex.UUID
import Config.Files import Config.Files
import P2P.IO
import Utility.ThreadScheduler
#ifndef mingw32_HOST_OS #ifndef mingw32_HOST_OS
import Utility.Su import Utility.Su
import System.Posix.User import System.Posix.User
#endif #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 :: Command
cmd = noCommit $ dontCheck repoExists $ cmd = noCommit $ dontCheck repoExists $
command "enable-tor" SectionSetup "enable tor hidden service" command "enable-tor" SectionSetup "enable tor hidden service"
@ -30,6 +31,8 @@ cmd = noCommit $ dontCheck repoExists $
seek :: CmdParams -> CommandSeek seek :: CmdParams -> CommandSeek
seek = withWords start 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 :: [String] -> CommandStart
start os = do start os = do
uuid <- getUUID uuid <- getUUID
@ -42,11 +45,12 @@ start os = do
Nothing -> giveup "Need user-id parameter." Nothing -> giveup "Need user-id parameter."
Just userid -> go uuid userid Just userid -> go uuid userid
else do else do
liftIO $ putStrLn "Need root access to enable tor..." showStart "enable-tor" ""
showLongNote "Need root access to enable tor..."
gitannex <- liftIO readProgramFile gitannex <- liftIO readProgramFile
let ps = [Param (cmdname cmd), Param (show curruserid)] let ps = [Param (cmdname cmd), Param (show curruserid)]
ifM (liftIO $ runAsRoot gitannex ps) ifM (liftIO $ runAsRoot gitannex ps)
( stop ( next $ next checkHiddenService
, giveup $ unwords $ , giveup $ unwords $
[ "Failed to run as root:" , gitannex ] ++ toCommand ps [ "Failed to run as root:" , gitannex ] ++ toCommand ps
) )
@ -59,3 +63,27 @@ start os = do
addHiddenService torAppName userid (fromUUID uuid) addHiddenService torAppName userid (fromUUID uuid)
storeP2PAddress $ TorAnnex onionaddr onionport storeP2PAddress $ TorAnnex onionaddr onionport
stop 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

View file

@ -68,6 +68,35 @@ closeConnection conn = do
hClose (connIhdl conn) hClose (connIhdl conn)
hClose (connOhdl 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 :: Socket -> IO Handle
setupHandle s = do setupHandle s = do
h <- socketToHandle s ReadWriteMode h <- socketToHandle s ReadWriteMode

View file

@ -48,22 +48,8 @@ server th@(TransportHandle (LocalRepo r) _) = do
replicateM_ maxConnections $ replicateM_ maxConnections $
forkIO $ forever $ serveClient th u r q 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" debugM "remotedaemon" "Tor hidden service running"
forever $ do serveUnixSocket sock $ \conn -> do
(conn, _) <- S.accept soc
h <- setupHandle conn
ok <- atomically $ ifM (isFullTBMQueue q) ok <- atomically $ ifM (isFullTBMQueue q)
( return False ( return False
, do , do

View file

@ -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) ### 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! 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]]

View file

@ -4,7 +4,6 @@ Mostly working!
Current todo list: 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 * 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 object is already in progress, the message about this is output by the
remotedaemon --debug, but not forwarded to the peer, which shows remotedaemon --debug, but not forwarded to the peer, which shows