summaryrefslogtreecommitdiff
path: root/Propellor/Property/Cmd.hs
diff options
context:
space:
mode:
Diffstat (limited to 'Propellor/Property/Cmd.hs')
-rw-r--r--Propellor/Property/Cmd.hs19
1 files changed, 4 insertions, 15 deletions
diff --git a/Propellor/Property/Cmd.hs b/Propellor/Property/Cmd.hs
index dc5073d3..875c1f9a 100644
--- a/Propellor/Property/Cmd.hs
+++ b/Propellor/Property/Cmd.hs
@@ -1,17 +1,17 @@
+{-# LANGUAGE PackageImports #-}
+
module Propellor.Property.Cmd (
cmdProperty,
cmdProperty',
scriptProperty,
userScriptProperty,
- serviceRunning,
) where
-import Control.Monad
import Control.Applicative
import Data.List
+import "mtl" Control.Monad.Reader
import Propellor.Types
-import Propellor.Engine
import Utility.Monad
import Utility.SafeCommand
import Utility.Env
@@ -25,7 +25,7 @@ cmdProperty cmd params = cmdProperty' cmd params []
-- | A property that can be satisfied by running a command,
-- with added environment.
cmdProperty' :: String -> [String] -> [(String, String)] -> Property
-cmdProperty' cmd params env = Property desc $ do
+cmdProperty' cmd params env = Property desc $ liftIO $ do
env' <- addEntries env <$> getEnvironment
ifM (boolSystemEnv cmd (map Param params) (Just env'))
( return MadeChange
@@ -46,14 +46,3 @@ userScriptProperty :: UserName -> [String] -> Property
userScriptProperty user script = cmdProperty "su" ["-c", shellcmd, user]
where
shellcmd = intercalate " ; " ("set -e" : "cd" : script)
-
--- | Ensures that a service is running.
---
--- Note that due to the general poor state of init scripts, the best
--- we can do is try to start the service, and if it fails, assume
--- this means it's already running.
-serviceRunning :: String -> Property
-serviceRunning svc = Property ("running " ++ svc) $ do
- void $ ensureProperty $
- scriptProperty ["service " ++ shellEscape svc ++ " start >/dev/null 2>&1 || true"]
- return NoChange