{-# LANGUAGE PackageImports #-}
module Propellor.Property.Cmd (
cmdProperty,
cmdProperty',
cmdPropertyEnv,
Script,
scriptProperty,
userScriptProperty,
cmdResult,
CommandParam(..),
boolSystem,
boolSystemEnv,
safeSystem,
safeSystemEnv,
shellEscape,
createProcess,
waitForProcess,
) where
import Data.List
import "mtl" Control.Monad.Reader
import Control.Applicative
import Prelude
import Propellor.Types
import Propellor.Property
import Utility.SafeCommand
import Utility.Env
import Utility.Process (createProcess, CreateProcess, waitForProcess)
cmdProperty :: String -> [String] -> UncheckedProperty UnixLike
cmdProperty :: String -> [String] -> UncheckedProperty UnixLike
cmdProperty String
cmd [String]
params = String
-> [String]
-> (CreateProcess -> CreateProcess)
-> UncheckedProperty UnixLike
cmdProperty' String
cmd [String]
params forall a. a -> a
id
cmdProperty' :: String -> [String] -> (CreateProcess -> CreateProcess) -> UncheckedProperty UnixLike
cmdProperty' :: String
-> [String]
-> (CreateProcess -> CreateProcess)
-> UncheckedProperty UnixLike
cmdProperty' String
cmd [String]
params CreateProcess -> CreateProcess
mkprocess = forall i. Property i -> UncheckedProperty i
unchecked forall a b. (a -> b) -> a -> b
$ forall {k} (metatypes :: k).
SingI metatypes =>
String -> Propellor Result -> Property (MetaTypes metatypes)
property String
desc forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$
Bool -> Result
cmdResult forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String
-> [CommandParam] -> (CreateProcess -> CreateProcess) -> IO Bool
boolSystem' String
cmd (forall a b. (a -> b) -> [a] -> [b]
map String -> CommandParam
Param [String]
params) CreateProcess -> CreateProcess
mkprocess
where
desc :: String
desc = [String] -> String
unwords forall a b. (a -> b) -> a -> b
$ String
cmd forall a. a -> [a] -> [a]
: [String]
params
cmdResult :: Bool -> Result
cmdResult :: Bool -> Result
cmdResult Bool
False = Result
FailedChange
cmdResult Bool
True = Result
NoChange
cmdPropertyEnv :: String -> [String] -> [(String, String)] -> UncheckedProperty UnixLike
cmdPropertyEnv :: String
-> [String] -> [(String, String)] -> UncheckedProperty UnixLike
cmdPropertyEnv String
cmd [String]
params [(String, String)]
env = forall i. Property i -> UncheckedProperty i
unchecked forall a b. (a -> b) -> a -> b
$ forall {k} (metatypes :: k).
SingI metatypes =>
String -> Propellor Result -> Property (MetaTypes metatypes)
property String
desc forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
[(String, String)]
env' <- forall k v. Eq k => [(k, v)] -> [(k, v)] -> [(k, v)]
addEntries [(String, String)]
env forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO [(String, String)]
getEnvironment
Bool -> Result
cmdResult forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> [CommandParam] -> Maybe [(String, String)] -> IO Bool
boolSystemEnv String
cmd (forall a b. (a -> b) -> [a] -> [b]
map String -> CommandParam
Param [String]
params) (forall a. a -> Maybe a
Just [(String, String)]
env')
where
desc :: String
desc = [String] -> String
unwords forall a b. (a -> b) -> a -> b
$ String
cmd forall a. a -> [a] -> [a]
: [String]
params
type Script = [String]
scriptProperty :: Script -> UncheckedProperty UnixLike
scriptProperty :: [String] -> UncheckedProperty UnixLike
scriptProperty [String]
script = String -> [String] -> UncheckedProperty UnixLike
cmdProperty String
"sh" [String
"-c", String
shellcmd]
where
shellcmd :: String
shellcmd = forall a. [a] -> [[a]] -> [a]
intercalate String
" ; " (String
"set -e" forall a. a -> [a] -> [a]
: [String]
script)
userScriptProperty :: User -> Script -> UncheckedProperty UnixLike
userScriptProperty :: User -> [String] -> UncheckedProperty UnixLike
userScriptProperty (User String
user) [String]
script = String -> [String] -> UncheckedProperty UnixLike
cmdProperty String
"su"
[String
"--login", String
"--shell", String
"/bin/sh", String
"-c", String
shellcmd, String
user]
where
shellcmd :: String
shellcmd = forall a. [a] -> [[a]] -> [a]
intercalate String
" ; " (String
"set -e" forall a. a -> [a] -> [a]
: String
"cd" forall a. a -> [a] -> [a]
: [String]
script)