This commit is contained in:
Joey Hess 2018-03-06 15:14:53 -04:00
parent 73704b22a9
commit ba53f60801
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
3 changed files with 20 additions and 20 deletions

View file

@ -21,6 +21,7 @@ import Config.Files
import P2P.IO
import qualified P2P.Protocol as P2P
import Utility.ThreadScheduler
import RemoteDaemon.Transport.Tor
import Control.Concurrent.Async
import qualified Network.Socket as S

View file

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

View file

@ -5,7 +5,9 @@
- Licensed under the GNU GPL version 3 or higher.
-}
module RemoteDaemon.Transport.Tor (server, transport) where
{-# LANGUAGE CPP #-}
module RemoteDaemon.Transport.Tor (server, transport, torSocketFile) where
import Common
import qualified Annex
@ -14,6 +16,7 @@ import Annex.ChangedRefs
import RemoteDaemon.Types
import RemoteDaemon.Common
import Utility.AuthToken
import Utility.Tor
import P2P.Protocol as P2P
import P2P.IO
import P2P.Annex
@ -30,6 +33,9 @@ import System.Log.Logger (debugM)
import Control.Concurrent.STM
import Control.Concurrent.STM.TBMQueue
import Control.Concurrent.Async
#ifndef mingw32_HOST_OS
import System.Posix.User
#endif
-- Run tor hidden service.
server :: Server
@ -178,3 +184,14 @@ transport (RemoteRepo r gc) url@(RemoteURI uri) th ichan ochan =
ok <- inLocalRepo th $
runBool [Param "fetch", Param $ Git.repoDescribe r]
send (DONESYNCING url ok)
torSocketFile :: Annex.Annex (Maybe FilePath)
torSocketFile = do
u <- getUUID
let ident = fromUUID u
#ifndef mingw32_HOST_OS
uid <- liftIO getRealUserID
#else
let uid = 0
#endif
liftIO $ getHiddenServiceSocketFile torAppName uid ident