This commit is contained in:
Joey Hess 2016-12-30 12:31:17 -04:00
parent dfbd303d66
commit b219be5100
No known key found for this signature in database
GPG key ID: C910D9222512E3C7
3 changed files with 19 additions and 10 deletions

View file

@ -12,6 +12,7 @@ module Command.EnableTor where
import Command import Command
import qualified Annex import qualified Annex
import P2P.Address import P2P.Address
import P2P.Annex
import Utility.Tor import Utility.Tor
import Annex.UUID import Annex.UUID
import Config.Files import Config.Files
@ -105,10 +106,8 @@ checkHiddenService = bracket setup cleanup go
startlistener = do startlistener = do
r <- Annex.gitRepo r <- Annex.gitRepo
u <- getUUID u <- getUUID
uid <- liftIO getRealUserID msock <- torSocketFile
let ident = fromUUID u case msock of
v <- liftIO $ getHiddenServiceSocketFile torAppName uid ident
case v of
Just sockfile -> ifM (liftIO $ haslistener sockfile) Just sockfile -> ifM (liftIO $ haslistener sockfile)
( liftIO $ async $ return () ( liftIO $ async $ return ()
, liftIO $ async $ runlistener sockfile u r , liftIO $ async $ runlistener sockfile u r

View file

@ -5,25 +5,32 @@
- Licensed under the GNU GPL version 3 or higher. - Licensed under the GNU GPL version 3 or higher.
-} -}
{-# LANGUAGE RankNTypes, FlexibleContexts #-} {-# LANGUAGE RankNTypes, FlexibleContexts, CPP #-}
module P2P.Annex module P2P.Annex
( RunMode(..) ( RunMode(..)
, P2PConnection(..) , P2PConnection(..)
, runFullProto , runFullProto
, torSocketFile
) where ) where
import Annex.Common import Annex.Common
import Annex.Content import Annex.Content
import Annex.Transfer import Annex.Transfer
import Annex.ChangedRefs import Annex.ChangedRefs
import P2P.Address
import P2P.Protocol import P2P.Protocol
import P2P.IO import P2P.IO
import Logs.Location import Logs.Location
import Types.NumCopies import Types.NumCopies
import Utility.Metered import Utility.Metered
import Utility.Tor
import Annex.UUID
import Control.Monad.Free import Control.Monad.Free
#ifndef mingw32_HOST_OS
import System.Posix.User
#endif
data RunMode data RunMode
= Serving UUID (Maybe ChangedRefsHandle) = Serving UUID (Maybe ChangedRefsHandle)
@ -152,3 +159,10 @@ runLocal runmode runner a = case a of
liftIO $ hSeek h AbsoluteSeek o liftIO $ hSeek h AbsoluteSeek o
b <- liftIO $ hGetContentsMetered h p' b <- liftIO $ hGetContentsMetered h p'
runner (sender b) runner (sender b)
torSocketFile :: Annex (Maybe FilePath)
torSocketFile = do
u <- getUUID
uid <- liftIO getRealUserID
let ident = fromUUID u
liftIO $ getHiddenServiceSocketFile torAppName uid ident

View file

@ -13,7 +13,6 @@ import Annex.Concurrent
import Annex.ChangedRefs import Annex.ChangedRefs
import RemoteDaemon.Types import RemoteDaemon.Types
import RemoteDaemon.Common import RemoteDaemon.Common
import Utility.Tor
import Utility.AuthToken import Utility.AuthToken
import P2P.Protocol as P2P import P2P.Protocol as P2P
import P2P.IO import P2P.IO
@ -26,7 +25,6 @@ import Messages
import Git import Git
import Git.Command import Git.Command
import System.PosixCompat.User
import Control.Concurrent import Control.Concurrent
import System.Log.Logger (debugM) import System.Log.Logger (debugM)
import Control.Concurrent.STM import Control.Concurrent.STM
@ -41,9 +39,7 @@ server ichan th@(TransportHandle (LocalRepo r) _) = go
checkstartservice = do checkstartservice = do
u <- liftAnnex th getUUID u <- liftAnnex th getUUID
uid <- getRealUserID msock <- liftAnnex th torSocketFile
let ident = fromUUID u
msock <- getHiddenServiceSocketFile torAppName uid ident
case msock of case msock of
Nothing -> do Nothing -> do
debugM "remotedaemon" "Tor hidden service not enabled" debugM "remotedaemon" "Tor hidden service not enabled"