propellor/src/Propellor/Property/Tor.hs

173 lines
5.1 KiB
Haskell
Raw Normal View History

2014-03-31 03:37:54 +00:00
module Propellor.Property.Tor where
2014-03-30 04:38:16 +00:00
2014-03-31 03:55:59 +00:00
import Propellor
2014-03-31 03:37:54 +00:00
import qualified Propellor.Property.File as File
import qualified Propellor.Property.Apt as Apt
import qualified Propellor.Property.Service as Service
import Utility.FileMode
2015-02-27 22:55:51 +00:00
import Utility.DataUnits
import System.Posix.Files
2015-01-29 05:04:59 +00:00
import Data.Char
2015-02-27 23:01:11 +00:00
import Data.List
type HiddenServiceName = String
2014-03-30 04:38:16 +00:00
2015-01-29 05:37:53 +00:00
type NodeName = String
2015-01-29 05:04:59 +00:00
2015-01-29 05:37:53 +00:00
-- | Sets up a tor bridge. (Not a relay or exit node.)
--
-- Uses port 443
isBridge :: Property NoInfo
2015-02-27 22:55:51 +00:00
isBridge = configured
[ ("BridgeRelay", "1")
, ("Exitpolicy", "reject *:*")
, ("ORPort", "443")
]
2014-03-30 19:53:35 +00:00
`describe` "tor bridge"
2015-02-27 22:55:51 +00:00
`requires` server
2015-01-29 05:37:53 +00:00
-- | Sets up a tor relay.
--
-- Uses port 443
isRelay :: Property NoInfo
2015-02-27 22:55:51 +00:00
isRelay = configured
[ ("BridgeRelay", "0")
, ("Exitpolicy", "reject *:*")
, ("ORPort", "443")
]
2015-01-29 05:37:53 +00:00
`describe` "tor relay"
2015-02-27 22:55:51 +00:00
`requires` server
2015-01-29 05:04:59 +00:00
2015-02-27 22:55:51 +00:00
-- | Makes the tor node be named, with a known private key.
2015-01-29 05:04:59 +00:00
--
-- This can be moved to a different IP without needing to wait to
-- accumulate trust.
2015-02-27 22:55:51 +00:00
named :: NodeName -> Property HasInfo
named n = configured [("Nickname", n')]
`describe` ("tor node named " ++ n')
`requires` torPrivKey (Context ("tor " ++ n))
2015-01-29 05:37:53 +00:00
where
2015-02-27 22:55:51 +00:00
n' = saneNickname n
2015-01-29 05:04:59 +00:00
torPrivKey :: Context -> Property HasInfo
torPrivKey context = f `File.hasPrivContent` context
`onChange` File.ownerGroup f user (userGroup user)
2015-01-29 05:04:59 +00:00
-- install tor first, so the directory exists with right perms
`requires` Apt.installed ["tor"]
where
f = "/var/lib/tor/keys/secret_id_key"
2014-03-30 04:38:16 +00:00
2015-02-27 22:55:51 +00:00
-- | A tor server (bridge, relay, or exit)
-- Don't use if you just want to run tor for personal use.
server :: Property NoInfo
server = configured [("SocksPort", "0")]
`requires` Apt.installed ["tor", "ntp"]
`describe` "tor server"
-- | Specifies configuration settings. Any lines in the config file
-- that set other values for the specified settings will be removed,
-- while other settings are left as-is. Tor is restarted when
-- configuration is changed.
configured :: [(String, String)] -> Property NoInfo
configured settings = File.fileProperty "tor configured" go mainConfig
`onChange` restarted
where
ks = map fst settings
2015-02-27 23:01:11 +00:00
go ls = sort $ map toconfig $
2015-02-27 22:55:51 +00:00
filter (\(k, _) -> k `notElem` ks) (map fromconfig ls)
++ settings
toconfig (k, v) = k ++ " " ++ v
fromconfig = separate (== ' ')
2015-02-27 23:14:20 +00:00
data BwLimit
= PerSecond String
| PerDay String
| PerMonth String
2015-02-27 22:55:51 +00:00
-- | Limit incoming and outgoing traffic to the specified
2015-02-27 23:14:20 +00:00
-- amount each.
2015-02-27 22:55:51 +00:00
--
2015-02-27 23:14:20 +00:00
-- For example, PerSecond "30 kibibytes" is the minimum limit
-- for a useful relay.
2015-02-27 22:55:51 +00:00
bandwidthRate :: BwLimit -> Property NoInfo
2015-02-27 23:14:20 +00:00
bandwidthRate (PerSecond s) = bandwidthRate' s 1
bandwidthRate (PerDay s) = bandwidthRate' s (24*60*60)
bandwidthRate (PerMonth s) = bandwidthRate' s (31*24*60*60)
bandwidthRate' :: String -> Integer -> Property NoInfo
bandwidthRate' s divby = case readSize dataUnits s of
2015-02-27 23:17:42 +00:00
Just sz -> let v = show (sz `div` divby) ++ " bytes"
in configured [("BandwidthRate", v)]
`describe` ("tor BandwidthRate " ++ v)
2015-02-27 22:55:51 +00:00
Nothing -> property ("unable to parse " ++ s) noChange
hiddenServiceAvailable :: HiddenServiceName -> Int -> Property NoInfo
hiddenServiceAvailable hn port = hiddenServiceHostName prop
where
2015-02-27 22:55:51 +00:00
prop = configured
[ ("HiddenServiceDir", varLib </> hn)
, ("HiddenServicePort", unwords [show port, "127.0.0.1:" ++ show port])
2014-11-10 20:27:36 +00:00
]
`describe` "hidden service available"
hiddenServiceHostName p = adjustPropertySatisfy p $ \satisfy -> do
r <- satisfy
h <- liftIO $ readFile (varLib </> hn </> "hostname")
warningMessage $ unwords ["hidden service hostname:", h]
return r
hiddenService :: HiddenServiceName -> Int -> Property NoInfo
2015-02-27 22:55:51 +00:00
hiddenService hn port = configured
[ ("HiddenServiceDir", varLib </> hn)
, ("HiddenServicePort", unwords [show port, "127.0.0.1:" ++ show port])
]
`describe` unwords ["hidden service available:", hn, show port]
hiddenServiceData :: IsContext c => HiddenServiceName -> c -> Property HasInfo
hiddenServiceData hn context = combineProperties desc
[ installonion "hostname"
, installonion "private_key"
]
where
desc = unwords ["hidden service data available in", varLib </> hn]
installonion f = withPrivData (PrivFile $ varLib </> hn </> f) context $ \getcontent ->
property desc $ getcontent $ install $ varLib </> hn </> f
install f content = ifM (liftIO $ doesFileExist f)
( noChange
, ensureProperties
[ property desc $ makeChange $ do
createDirectoryIfMissing True (takeDirectory f)
writeFileProtected f content
, File.mode (takeDirectory f) $ combineModes
[ownerReadMode, ownerWriteMode, ownerExecuteMode]
, File.ownerGroup (takeDirectory f) user (userGroup user)
, File.ownerGroup f user (userGroup user)
]
)
restarted :: Property NoInfo
restarted = Service.restarted "tor"
mainConfig :: FilePath
mainConfig = "/etc/tor/torrc"
varLib :: FilePath
varLib = "/var/lib/tor"
varRun :: FilePath
varRun = "/var/run/tor"
user :: User
user = User "debian-tor"
2015-01-29 05:04:59 +00:00
type NickName = String
-- | Convert String to a valid tor NickName.
saneNickname :: String -> NickName
saneNickname s
| null n = "unnamed"
| otherwise = n
where
legal c = isNumber c || isAsciiUpper c || isAsciiLower c
n = take 19 $ filter legal s