aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--Command/EnableTor.hs1
-rw-r--r--P2P/Annex.hs20
-rw-r--r--P2P/Protocol.hs2
-rw-r--r--RemoteDaemon/Transport/Tor.hs19
-rw-r--r--doc/devblog/day_486__time_to_ditch_rsync.mdwn14
5 files changed, 35 insertions, 21 deletions
diff --git a/Command/EnableTor.hs b/Command/EnableTor.hs
index b73d00277..6ddf3e136 100644
--- a/Command/EnableTor.hs
+++ b/Command/EnableTor.hs
@@ -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
diff --git a/P2P/Annex.hs b/P2P/Annex.hs
index 82f669eaf..9971762f5 100644
--- a/P2P/Annex.hs
+++ b/P2P/Annex.hs
@@ -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
diff --git a/P2P/Protocol.hs b/P2P/Protocol.hs
index e74979170..f762c3783 100644
--- a/P2P/Protocol.hs
+++ b/P2P/Protocol.hs
@@ -39,7 +39,7 @@ newtype Offset = Offset Integer
newtype Len = Len Integer
deriving (Show)
--- | Service as used by the connect message is gitremote-helpers(1)
+-- | Service as used by the connect message in gitremote-helpers(1)
data Service = UploadPack | ReceivePack
deriving (Show)
diff --git a/RemoteDaemon/Transport/Tor.hs b/RemoteDaemon/Transport/Tor.hs
index b0fa3c189..623ff03e3 100644
--- a/RemoteDaemon/Transport/Tor.hs
+++ b/RemoteDaemon/Transport/Tor.hs
@@ -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
diff --git a/doc/devblog/day_486__time_to_ditch_rsync.mdwn b/doc/devblog/day_486__time_to_ditch_rsync.mdwn
new file mode 100644
index 000000000..bd7cf0d4b
--- /dev/null
+++ b/doc/devblog/day_486__time_to_ditch_rsync.mdwn
@@ -0,0 +1,14 @@
+I'm excited by this new design
+[[todo/accellerate_ssh_remotes_with_git-annex-shell_mass_protocol]].
+
+git-annex's use of rsync got transfers over ssh working quickly early on,
+but other than resuming interrupted transfers, using rsync doesn't really
+gain git-annex much, since annexed objects don't change over time. And
+rsync has always involved a certian amount of overhead that a custom
+protocol would avoid.
+
+It's especially handy that such a protocol was already developed for
+`git-annex p2p` when using tor. I've not heard of a lot of people using that
+feature (but maybe people who do have reason not to talk about it), but
+it's a good solid thing, implemented very generically with a free monad,
+and reusing it for git-annex-shell would be great.