refactor
This commit is contained in:
parent
dfbd303d66
commit
b219be5100
3 changed files with 19 additions and 10 deletions
|
@ -12,6 +12,7 @@ module Command.EnableTor where
|
|||
import Command
|
||||
import qualified Annex
|
||||
import P2P.Address
|
||||
import P2P.Annex
|
||||
import Utility.Tor
|
||||
import Annex.UUID
|
||||
import Config.Files
|
||||
|
@ -105,10 +106,8 @@ checkHiddenService = bracket setup cleanup go
|
|||
startlistener = do
|
||||
r <- Annex.gitRepo
|
||||
u <- getUUID
|
||||
uid <- liftIO getRealUserID
|
||||
let ident = fromUUID u
|
||||
v <- liftIO $ getHiddenServiceSocketFile torAppName uid ident
|
||||
case v of
|
||||
msock <- torSocketFile
|
||||
case msock of
|
||||
Just sockfile -> ifM (liftIO $ haslistener sockfile)
|
||||
( liftIO $ async $ return ()
|
||||
, liftIO $ async $ runlistener sockfile u r
|
||||
|
|
16
P2P/Annex.hs
16
P2P/Annex.hs
|
@ -5,25 +5,32 @@
|
|||
- Licensed under the GNU GPL version 3 or higher.
|
||||
-}
|
||||
|
||||
{-# LANGUAGE RankNTypes, FlexibleContexts #-}
|
||||
{-# LANGUAGE RankNTypes, FlexibleContexts, CPP #-}
|
||||
|
||||
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)
|
||||
|
@ -152,3 +159,10 @@ 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
|
||||
uid <- liftIO getRealUserID
|
||||
let ident = fromUUID u
|
||||
liftIO $ getHiddenServiceSocketFile torAppName uid ident
|
||||
|
|
|
@ -13,7 +13,6 @@ import Annex.Concurrent
|
|||
import Annex.ChangedRefs
|
||||
import RemoteDaemon.Types
|
||||
import RemoteDaemon.Common
|
||||
import Utility.Tor
|
||||
import Utility.AuthToken
|
||||
import P2P.Protocol as P2P
|
||||
import P2P.IO
|
||||
|
@ -26,7 +25,6 @@ import Messages
|
|||
import Git
|
||||
import Git.Command
|
||||
|
||||
import System.PosixCompat.User
|
||||
import Control.Concurrent
|
||||
import System.Log.Logger (debugM)
|
||||
import Control.Concurrent.STM
|
||||
|
@ -41,9 +39,7 @@ server ichan th@(TransportHandle (LocalRepo r) _) = go
|
|||
|
||||
checkstartservice = do
|
||||
u <- liftAnnex th getUUID
|
||||
uid <- getRealUserID
|
||||
let ident = fromUUID u
|
||||
msock <- getHiddenServiceSocketFile torAppName uid ident
|
||||
msock <- liftAnnex th torSocketFile
|
||||
case msock of
|
||||
Nothing -> do
|
||||
debugM "remotedaemon" "Tor hidden service not enabled"
|
||||
|
|
Loading…
Reference in a new issue