improvements

This commit is contained in:
Joey Hess 2014-03-30 00:52:02 -04:00
parent 08a0a46efe
commit e812acce3e
4 changed files with 14 additions and 14 deletions

View File

@ -25,7 +25,6 @@ getProperties "clam" =
, Apt.stdSourcesList Apt.Unstable `onChange` Apt.upgrade
, Apt.installed ["etckeeper"]
, Apt.installed ["ssh"]
, Apt.installed ["git", "myrepos"]
, GitHome.installedFor "root"
-- Harden the system, but only once root's authorized_keys
-- is safely in place.
@ -38,7 +37,6 @@ getProperties "clam" =
, lineInFile "/etc/sudoers" "joey ALL=(ALL:ALL) ALL"
, GitHome.installedFor "joey"
-- Clam is a tor bridge.
, Apt.installed ["tor"]
, Tor.isBridge
-- Should come last as it reboots.
, Apt.installed ["systemd-sysv"] `onChange` Reboot.scheduled "+10"

View File

@ -147,6 +147,9 @@ property `onChange` hook = IOProperty (propertyDesc property) $ do
return $ combineResult r r'
_ -> return r
requires :: Property -> Property -> Property
x `requires` y = combineProperties (propertyDesc x) [y, x]
{- Makes a Property only be performed when a test succeeds. -}
check :: IO Bool -> Property -> Property
check c property = IOProperty (propertyDesc property) $ ifM c

View File

@ -11,11 +11,13 @@ import Utility.SafeCommand
import Utility.Directory
import Utility.Monad
import Utility.Exception
import qualified Property.Apt as Apt
{- Clones Joey Hess's git home directory, and runs its fixups script. -}
installedFor :: UserName -> Property
installedFor user = check (not <$> hasGitDir user) $
IOProperty ("githome " ++ user) (go =<< homedir user)
`requires` Apt.installed ["git", "myrepos"]
where
go Nothing = noChange
go (Just home) = do

View File

@ -1,21 +1,18 @@
module Property.Tor where
import Control.Applicative
import Control.Monad
import System.FilePath
import Property
import Property.User
import Utility.SafeCommand
import Utility.Exception
import qualified Property.Apt as Apt
isBridge :: Property
isBridge = fileHasContent "/etc/tor/torrc"
[ "SocksPort 0"
, "ORPort 443"
, "BridgeRelay 1"
, "Exitpolicy reject *:*"
] `onChange` restartTor
isBridge = setup `requires` Apt.installed ["tor"]
where
setup = fileHasContent "/etc/tor/torrc"
[ "SocksPort 0"
, "ORPort 443"
, "BridgeRelay 1"
, "Exitpolicy reject *:*"
] `onChange` restartTor
restartTor :: Property
restartTor = cmdProperty "service" [Param "tor", Param "restart"]