enable-tor: No longer needs to be run as root.
When run by not root, su's to root automatically. This commit was sponsored by Brock Spratlen on Patreon.
This commit is contained in:
parent
944a6503b9
commit
f7ca2b92fb
6 changed files with 92 additions and 6 deletions
|
@ -21,6 +21,7 @@ git-annex (6.20161211) UNRELEASED; urgency=medium
|
|||
present in the local repo even when it was not.
|
||||
* enable-tor: Put tor sockets in /var/lib/tor-annex/, rather
|
||||
than in /etc/tor/hidden_service/.
|
||||
* enable-tor: No longer needs to be run as root.
|
||||
* Fix build with directory-1.3.
|
||||
* Debian: Suggest tor and magic-wormhole.
|
||||
* Debian: Build webapp on armel.
|
||||
|
|
|
@ -5,12 +5,20 @@
|
|||
- Licensed under the GNU GPL version 3 or higher.
|
||||
-}
|
||||
|
||||
{-# LANGUAGE CPP #-}
|
||||
|
||||
module Command.EnableTor where
|
||||
|
||||
import Command
|
||||
import P2P.Address
|
||||
import Utility.Tor
|
||||
import Annex.UUID
|
||||
import Config.Files
|
||||
|
||||
#ifndef mingw32_HOST_OS
|
||||
import Utility.Su
|
||||
import System.Posix.User
|
||||
#endif
|
||||
|
||||
-- This runs as root, so avoid making any commits or initializing
|
||||
-- git-annex, or doing other things that create root-owned files.
|
||||
|
@ -23,9 +31,27 @@ seek :: CmdParams -> CommandSeek
|
|||
seek = withWords start
|
||||
|
||||
start :: [String] -> CommandStart
|
||||
start ps = case readish =<< headMaybe ps of
|
||||
Nothing -> giveup "Bad params"
|
||||
Just userid -> do
|
||||
start os = do
|
||||
#ifndef mingw32_HOST_OS
|
||||
curruserid <- liftIO getEffectiveUserID
|
||||
if curruserid == 0
|
||||
then case readish =<< headMaybe os of
|
||||
Nothing -> giveup "Need user-id parameter."
|
||||
Just userid -> go userid
|
||||
else do
|
||||
liftIO $ putStrLn "Need root access to enable tor..."
|
||||
gitannex <- liftIO readProgramFile
|
||||
let ps = [Param (cmdname cmd), Param (show curruserid)]
|
||||
ifM (liftIO $ runAsRoot gitannex ps)
|
||||
( stop
|
||||
, giveup $ unwords $
|
||||
[ "Failed to run as root:" , gitannex ] ++ toCommand ps
|
||||
)
|
||||
#else
|
||||
go 0
|
||||
#endif
|
||||
where
|
||||
go userid = do
|
||||
uuid <- getUUID
|
||||
when (uuid == NoUUID) $
|
||||
giveup "This can only be run in a git-annex repository."
|
||||
|
|
54
Utility/Su.hs
Normal file
54
Utility/Su.hs
Normal file
|
@ -0,0 +1,54 @@
|
|||
{- su to root
|
||||
-
|
||||
- Copyright 2016 Joey Hess <id@joeyh.name>
|
||||
-
|
||||
- License: BSD-2-clause
|
||||
-}
|
||||
|
||||
module Utility.Su where
|
||||
|
||||
import Common
|
||||
import Utility.Env
|
||||
import Utility.Path
|
||||
|
||||
import System.Posix.Terminal
|
||||
|
||||
-- Runs a command as root, fairly portably.
|
||||
--
|
||||
-- Does not use sudo commands if something else is available, because
|
||||
-- the user may not be in sudoers and we couldn't differentiate between
|
||||
-- that and the command failing. Although, some commands like gksu
|
||||
-- decide based on the system's configuration whether sudo should be used.
|
||||
runAsRoot :: String -> [CommandParam] -> IO Bool
|
||||
runAsRoot cmd ps = go =<< firstM (inPath . fst) =<< selectcmds
|
||||
where
|
||||
go Nothing = return False
|
||||
go (Just (cmd', ps')) = boolSystem cmd' ps'
|
||||
|
||||
selectcmds = ifM (inx <||> (not <$> atconsole))
|
||||
( return (graphicalcmds ++ consolecmds)
|
||||
, return consolecmds
|
||||
)
|
||||
|
||||
inx = isJust <$> getEnv "DISPLAY"
|
||||
atconsole = queryTerminal stdInput
|
||||
|
||||
-- These will only work when the user is logged into a desktop.
|
||||
graphicalcmds =
|
||||
[ ("gksu", [Param shellcmd])
|
||||
, ("kdesu", [Param shellcmd])
|
||||
-- Available in Debian's menu package; knows about lots of
|
||||
-- ways to gain root.
|
||||
, ("su-to-root", [Param "-X", Param "-c", Param shellcmd])
|
||||
-- OSX native way to run a command as root, prompts in GUI
|
||||
, ("osascript", [Param "-e", Param ("do shell script \"" ++ shellcmd ++ "\" with administrator privileges")])
|
||||
]
|
||||
|
||||
-- These will only work when run in a console.
|
||||
consolecmds =
|
||||
[ ("su", [Param "-c", Param "--", Param cmd] ++ ps)
|
||||
, ("sudo", [Param cmd] ++ ps)
|
||||
, ("su-to-root", [Param "-c", Param shellcmd])
|
||||
]
|
||||
|
||||
shellcmd = unwords $ map shellEscape (cmd:toCommand ps)
|
|
@ -4,14 +4,18 @@ git-annex enable-tor - enable tor hidden service
|
|||
|
||||
# SYNOPSIS
|
||||
|
||||
git annex enable-tor
|
||||
|
||||
sudo git annex enable-tor $(id -u)
|
||||
|
||||
# DESCRIPTION
|
||||
|
||||
This command enables a tor hidden service for git-annex.
|
||||
|
||||
It has to be run by root, since it modifies `/etc/tor/torrc`.
|
||||
Pass it your user id number, as output by `id -u`
|
||||
It modifies `/etc/tor/torrc` to register the hidden service. If run as a
|
||||
normal user, it will try to use sudo/su/etc to get root access to modify
|
||||
that file. If you run it as root, pass it your non-root user id number,
|
||||
as output by `id -u`
|
||||
|
||||
After this command is run, `git annex remotedaemon` can be run to serve the
|
||||
tor hidden service, and then `git-annex p2p --gen-address` can be run to
|
||||
|
|
|
@ -23,7 +23,7 @@ to accomplish this.
|
|||
|
||||
In each git-annex repository, run these commands:
|
||||
|
||||
sudo git annex enable-tor $(id -u)
|
||||
git annex enable-tor
|
||||
git annex remotedaemon
|
||||
|
||||
Now git-annex is running as a Tor hidden service, but
|
||||
|
|
|
@ -1072,6 +1072,7 @@ Executable git-annex
|
|||
Utility.Shell
|
||||
Utility.SimpleProtocol
|
||||
Utility.SshConfig
|
||||
Utility.Su
|
||||
Utility.SystemDirectory
|
||||
Utility.TList
|
||||
Utility.Tense
|
||||
|
|
Loading…
Reference in a new issue