Export CommandParam, boolSystem, safeSystem and shellEscape from Propellor.Property.Cmd, so they are available for use in constricting your own Properties when using propellor as a library.
Several imports of Utility.SafeCommand now redundant.
This commit is contained in:
parent
d7ff70c727
commit
626f1af56f
|
@ -4,6 +4,9 @@ propellor (2.5.0) UNRELEASED; urgency=medium
|
||||||
more generic cmdProperty' (API change)
|
more generic cmdProperty' (API change)
|
||||||
* Add docker image related properties.
|
* Add docker image related properties.
|
||||||
Thanks, Antoine Eiche.
|
Thanks, Antoine Eiche.
|
||||||
|
* Export CommandParam, boolSystem, safeSystem and shellEscape from
|
||||||
|
Propellor.Property.Cmd, so they are available for use in constricting
|
||||||
|
your own Properties when using propellor as a library.
|
||||||
|
|
||||||
-- Joey Hess <id@joeyh.name> Thu, 07 May 2015 12:08:34 -0400
|
-- Joey Hess <id@joeyh.name> Thu, 07 May 2015 12:08:34 -0400
|
||||||
|
|
||||||
|
|
|
@ -6,7 +6,6 @@ module Propellor.Bootstrap (
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Propellor
|
import Propellor
|
||||||
import Utility.SafeCommand
|
|
||||||
|
|
||||||
import System.Posix.Files
|
import System.Posix.Files
|
||||||
import Data.List
|
import Data.List
|
||||||
|
|
|
@ -18,7 +18,6 @@ import Propellor.Types.CmdLine
|
||||||
import qualified Propellor.Property.Docker as Docker
|
import qualified Propellor.Property.Docker as Docker
|
||||||
import qualified Propellor.Property.Chroot as Chroot
|
import qualified Propellor.Property.Chroot as Chroot
|
||||||
import qualified Propellor.Shim as Shim
|
import qualified Propellor.Shim as Shim
|
||||||
import Utility.SafeCommand
|
|
||||||
|
|
||||||
usage :: Handle -> IO ()
|
usage :: Handle -> IO ()
|
||||||
usage h = hPutStrLn h $ unlines
|
usage h = hPutStrLn h $ unlines
|
||||||
|
|
|
@ -3,7 +3,6 @@ module Propellor.Git where
|
||||||
import Propellor
|
import Propellor
|
||||||
import Propellor.PrivData.Paths
|
import Propellor.PrivData.Paths
|
||||||
import Propellor.Gpg
|
import Propellor.Gpg
|
||||||
import Utility.SafeCommand
|
|
||||||
import Utility.FileMode
|
import Utility.FileMode
|
||||||
|
|
||||||
getCurrentBranch :: IO String
|
getCurrentBranch :: IO String
|
||||||
|
|
|
@ -4,7 +4,6 @@ import Propellor
|
||||||
import qualified Propellor.Property.File as File
|
import qualified Propellor.Property.File as File
|
||||||
import qualified Propellor.Property.Apt as Apt
|
import qualified Propellor.Property.Apt as Apt
|
||||||
import qualified Propellor.Property.Service as Service
|
import qualified Propellor.Property.Service as Service
|
||||||
import Utility.SafeCommand
|
|
||||||
|
|
||||||
type ConfigFile = [String]
|
type ConfigFile = [String]
|
||||||
|
|
||||||
|
|
|
@ -19,7 +19,6 @@ import Propellor.Property.Chroot.Util
|
||||||
import qualified Propellor.Property.Debootstrap as Debootstrap
|
import qualified Propellor.Property.Debootstrap as Debootstrap
|
||||||
import qualified Propellor.Property.Systemd.Core as Systemd
|
import qualified Propellor.Property.Systemd.Core as Systemd
|
||||||
import qualified Propellor.Shim as Shim
|
import qualified Propellor.Shim as Shim
|
||||||
import Utility.SafeCommand
|
|
||||||
|
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
import Data.List.Utils
|
import Data.List.Utils
|
||||||
|
|
|
@ -1,11 +1,20 @@
|
||||||
{-# LANGUAGE PackageImports #-}
|
{-# LANGUAGE PackageImports #-}
|
||||||
|
|
||||||
module Propellor.Property.Cmd (
|
module Propellor.Property.Cmd (
|
||||||
|
-- * Properties for running commands and scripts
|
||||||
cmdProperty,
|
cmdProperty,
|
||||||
cmdProperty',
|
cmdProperty',
|
||||||
cmdPropertyEnv,
|
cmdPropertyEnv,
|
||||||
|
Script,
|
||||||
scriptProperty,
|
scriptProperty,
|
||||||
userScriptProperty,
|
userScriptProperty,
|
||||||
|
-- * Lower-level interface for running commands
|
||||||
|
CommandParam(..),
|
||||||
|
boolSystem,
|
||||||
|
boolSystemEnv,
|
||||||
|
safeSystem,
|
||||||
|
safeSystemEnv,
|
||||||
|
shellEscape
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
|
@ -40,15 +49,18 @@ cmdPropertyEnv cmd params env = property desc $ liftIO $ do
|
||||||
where
|
where
|
||||||
desc = unwords $ cmd : params
|
desc = unwords $ cmd : params
|
||||||
|
|
||||||
-- | A property that can be satisfied by running a series of shell commands.
|
-- | A series of shell commands. (Without a leading hashbang.)
|
||||||
scriptProperty :: [String] -> Property NoInfo
|
type Script = [String]
|
||||||
|
|
||||||
|
-- | A property that can be satisfied by running a script.
|
||||||
|
scriptProperty :: Script -> Property NoInfo
|
||||||
scriptProperty script = cmdProperty "sh" ["-c", shellcmd]
|
scriptProperty script = cmdProperty "sh" ["-c", shellcmd]
|
||||||
where
|
where
|
||||||
shellcmd = intercalate " ; " ("set -e" : script)
|
shellcmd = intercalate " ; " ("set -e" : script)
|
||||||
|
|
||||||
-- | A property that can satisfied by running a series of shell commands,
|
-- | A property that can satisfied by running a script
|
||||||
-- as user (cd'd to their home directory).
|
-- as user (cd'd to their home directory).
|
||||||
userScriptProperty :: User -> [String] -> Property NoInfo
|
userScriptProperty :: User -> Script -> Property NoInfo
|
||||||
userScriptProperty (User user) script = cmdProperty "su" ["--shell", "/bin/sh", "-c", shellcmd, user]
|
userScriptProperty (User user) script = cmdProperty "su" ["--shell", "/bin/sh", "-c", shellcmd, user]
|
||||||
where
|
where
|
||||||
shellcmd = intercalate " ; " ("set -e" : "cd" : script)
|
shellcmd = intercalate " ; " ("set -e" : "cd" : script)
|
||||||
|
|
|
@ -4,7 +4,6 @@ import Propellor
|
||||||
import qualified Propellor.Property.File as File
|
import qualified Propellor.Property.File as File
|
||||||
import qualified Propellor.Property.Apt as Apt
|
import qualified Propellor.Property.Apt as Apt
|
||||||
import Propellor.Bootstrap
|
import Propellor.Bootstrap
|
||||||
import Utility.SafeCommand
|
|
||||||
import Utility.FileMode
|
import Utility.FileMode
|
||||||
|
|
||||||
import Data.Char
|
import Data.Char
|
||||||
|
|
|
@ -15,7 +15,6 @@ import qualified Propellor.Property.Apt as Apt
|
||||||
import Propellor.Property.Chroot.Util
|
import Propellor.Property.Chroot.Util
|
||||||
import Propellor.Property.Mount
|
import Propellor.Property.Mount
|
||||||
import Utility.Path
|
import Utility.Path
|
||||||
import Utility.SafeCommand
|
|
||||||
import Utility.FileMode
|
import Utility.FileMode
|
||||||
|
|
||||||
import Data.List
|
import Data.List
|
||||||
|
|
|
@ -48,7 +48,6 @@ import qualified Propellor.Property.File as File
|
||||||
import qualified Propellor.Property.Apt as Apt
|
import qualified Propellor.Property.Apt as Apt
|
||||||
import qualified Propellor.Property.Cmd as Cmd
|
import qualified Propellor.Property.Cmd as Cmd
|
||||||
import qualified Propellor.Shim as Shim
|
import qualified Propellor.Shim as Shim
|
||||||
import Utility.SafeCommand
|
|
||||||
import Utility.Path
|
import Utility.Path
|
||||||
import Utility.ThreadScheduler
|
import Utility.ThreadScheduler
|
||||||
|
|
||||||
|
|
|
@ -18,7 +18,6 @@ import Data.Char
|
||||||
import Data.List
|
import Data.List
|
||||||
|
|
||||||
import Propellor
|
import Propellor
|
||||||
import Utility.SafeCommand
|
|
||||||
import qualified Propellor.Property.Apt as Apt
|
import qualified Propellor.Property.Apt as Apt
|
||||||
import qualified Propellor.Property.Network as Network
|
import qualified Propellor.Property.Network as Network
|
||||||
|
|
||||||
|
|
|
@ -4,7 +4,6 @@ import Propellor
|
||||||
import Propellor.Property.File
|
import Propellor.Property.File
|
||||||
import qualified Propellor.Property.Apt as Apt
|
import qualified Propellor.Property.Apt as Apt
|
||||||
import qualified Propellor.Property.Service as Service
|
import qualified Propellor.Property.Service as Service
|
||||||
import Utility.SafeCommand
|
|
||||||
|
|
||||||
import Data.List
|
import Data.List
|
||||||
|
|
||||||
|
|
|
@ -1,7 +1,6 @@
|
||||||
module Propellor.Property.Mount where
|
module Propellor.Property.Mount where
|
||||||
|
|
||||||
import Propellor
|
import Propellor
|
||||||
import Utility.SafeCommand
|
|
||||||
|
|
||||||
type FsType = String
|
type FsType = String
|
||||||
type Source = String
|
type Source = String
|
||||||
|
|
|
@ -16,7 +16,6 @@ import qualified Propellor.Property.File as File
|
||||||
import qualified Propellor.Property.Reboot as Reboot
|
import qualified Propellor.Property.Reboot as Reboot
|
||||||
import Propellor.Property.Mount
|
import Propellor.Property.Mount
|
||||||
import Propellor.Property.Chroot.Util (stdPATH)
|
import Propellor.Property.Chroot.Util (stdPATH)
|
||||||
import Utility.SafeCommand
|
|
||||||
|
|
||||||
import System.Posix.Files (rename, fileExist)
|
import System.Posix.Files (rename, fileExist)
|
||||||
import Control.Exception (throw)
|
import Control.Exception (throw)
|
||||||
|
|
|
@ -4,7 +4,6 @@ import Propellor
|
||||||
import qualified Propellor.Property.Apt as Apt
|
import qualified Propellor.Property.Apt as Apt
|
||||||
import qualified Propellor.Property.Cron as Cron
|
import qualified Propellor.Property.Cron as Cron
|
||||||
import qualified Propellor.Property.Gpg as Gpg
|
import qualified Propellor.Property.Gpg as Gpg
|
||||||
import Utility.SafeCommand
|
|
||||||
|
|
||||||
import Data.List
|
import Data.List
|
||||||
|
|
||||||
|
|
|
@ -1,7 +1,6 @@
|
||||||
module Propellor.Property.Reboot where
|
module Propellor.Property.Reboot where
|
||||||
|
|
||||||
import Propellor
|
import Propellor
|
||||||
import Utility.SafeCommand
|
|
||||||
|
|
||||||
now :: Property NoInfo
|
now :: Property NoInfo
|
||||||
now = cmdProperty "reboot" []
|
now = cmdProperty "reboot" []
|
||||||
|
|
|
@ -1,7 +1,6 @@
|
||||||
module Propellor.Property.Service where
|
module Propellor.Property.Service where
|
||||||
|
|
||||||
import Propellor
|
import Propellor
|
||||||
import Utility.SafeCommand
|
|
||||||
|
|
||||||
type ServiceName = String
|
type ServiceName = String
|
||||||
|
|
||||||
|
|
|
@ -3,7 +3,6 @@ module Propellor.Property.SiteSpecific.GitHome where
|
||||||
import Propellor
|
import Propellor
|
||||||
import qualified Propellor.Property.Apt as Apt
|
import qualified Propellor.Property.Apt as Apt
|
||||||
import Propellor.Property.User
|
import Propellor.Property.User
|
||||||
import Utility.SafeCommand
|
|
||||||
|
|
||||||
-- | Clones Joey Hess's git home directory, and runs its fixups script.
|
-- | Clones Joey Hess's git home directory, and runs its fixups script.
|
||||||
installedFor :: User -> Property NoInfo
|
installedFor :: User -> Property NoInfo
|
||||||
|
|
|
@ -15,7 +15,6 @@ import qualified Propellor.Property.User as User
|
||||||
import qualified Propellor.Property.Obnam as Obnam
|
import qualified Propellor.Property.Obnam as Obnam
|
||||||
import qualified Propellor.Property.Apache as Apache
|
import qualified Propellor.Property.Apache as Apache
|
||||||
import qualified Propellor.Property.Postfix as Postfix
|
import qualified Propellor.Property.Postfix as Postfix
|
||||||
import Utility.SafeCommand
|
|
||||||
import Utility.FileMode
|
import Utility.FileMode
|
||||||
|
|
||||||
import Data.List
|
import Data.List
|
||||||
|
|
|
@ -24,7 +24,6 @@ import Propellor
|
||||||
import qualified Propellor.Property.File as File
|
import qualified Propellor.Property.File as File
|
||||||
import qualified Propellor.Property.Service as Service
|
import qualified Propellor.Property.Service as Service
|
||||||
import Propellor.Property.User
|
import Propellor.Property.User
|
||||||
import Utility.SafeCommand
|
|
||||||
import Utility.FileMode
|
import Utility.FileMode
|
||||||
|
|
||||||
import System.PosixCompat
|
import System.PosixCompat
|
||||||
|
|
|
@ -25,7 +25,6 @@ import qualified Propellor.Property.Chroot as Chroot
|
||||||
import qualified Propellor.Property.Apt as Apt
|
import qualified Propellor.Property.Apt as Apt
|
||||||
import qualified Propellor.Property.File as File
|
import qualified Propellor.Property.File as File
|
||||||
import Propellor.Property.Systemd.Core
|
import Propellor.Property.Systemd.Core
|
||||||
import Utility.SafeCommand
|
|
||||||
import Utility.FileMode
|
import Utility.FileMode
|
||||||
|
|
||||||
import Data.List
|
import Data.List
|
||||||
|
|
|
@ -8,7 +8,6 @@ module Propellor.Shim (setup, cleanEnv, file) where
|
||||||
|
|
||||||
import Propellor
|
import Propellor
|
||||||
import Utility.LinuxMkLibs
|
import Utility.LinuxMkLibs
|
||||||
import Utility.SafeCommand
|
|
||||||
import Utility.FileMode
|
import Utility.FileMode
|
||||||
import Utility.FileSystemEncoding
|
import Utility.FileSystemEncoding
|
||||||
|
|
||||||
|
|
|
@ -1,7 +1,6 @@
|
||||||
module Propellor.Ssh where
|
module Propellor.Ssh where
|
||||||
|
|
||||||
import Propellor
|
import Propellor
|
||||||
import Utility.SafeCommand
|
|
||||||
import Utility.UserInfo
|
import Utility.UserInfo
|
||||||
|
|
||||||
import System.PosixCompat
|
import System.PosixCompat
|
||||||
|
|
|
@ -17,16 +17,15 @@ import Data.Char
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
import Prelude
|
import Prelude
|
||||||
|
|
||||||
{- A type for parameters passed to a shell command. A command can
|
-- | Parameters that can be passed to a shell command.
|
||||||
- be passed either some Params (multiple parameters can be included,
|
data CommandParam
|
||||||
- whitespace-separated, or a single Param (for when parameters contain
|
= Params String -- ^ Contains multiple parameters, separated by whitespace
|
||||||
- whitespace), or a File.
|
| Param String -- ^ A single parameter
|
||||||
-}
|
| File FilePath -- ^ The name of a file
|
||||||
data CommandParam = Params String | Param String | File FilePath
|
|
||||||
deriving (Eq, Show, Ord)
|
deriving (Eq, Show, Ord)
|
||||||
|
|
||||||
{- Used to pass a list of CommandParams to a function that runs
|
-- | Used to pass a list of CommandParams to a function that runs
|
||||||
- a command and expects Strings. -}
|
-- a command and expects Strings. -}
|
||||||
toCommand :: [CommandParam] -> [String]
|
toCommand :: [CommandParam] -> [String]
|
||||||
toCommand = concatMap unwrap
|
toCommand = concatMap unwrap
|
||||||
where
|
where
|
||||||
|
@ -43,9 +42,10 @@ toCommand = concatMap unwrap
|
||||||
-- path separator on Windows.
|
-- path separator on Windows.
|
||||||
pathseps = pathSeparator:"./"
|
pathseps = pathSeparator:"./"
|
||||||
|
|
||||||
{- Run a system command, and returns True or False
|
-- | Run a system command, and returns True or False if it succeeded or failed.
|
||||||
- if it succeeded or failed.
|
--
|
||||||
-}
|
-- This and other command running functions in this module log the commands
|
||||||
|
-- run at debug level, using System.Log.Logger.
|
||||||
boolSystem :: FilePath -> [CommandParam] -> IO Bool
|
boolSystem :: FilePath -> [CommandParam] -> IO Bool
|
||||||
boolSystem command params = boolSystem' command params id
|
boolSystem command params = boolSystem' command params id
|
||||||
|
|
||||||
|
@ -59,7 +59,7 @@ boolSystemEnv :: FilePath -> [CommandParam] -> Maybe [(String, String)] -> IO Bo
|
||||||
boolSystemEnv command params environ = boolSystem' command params $
|
boolSystemEnv command params environ = boolSystem' command params $
|
||||||
\p -> p { env = environ }
|
\p -> p { env = environ }
|
||||||
|
|
||||||
{- Runs a system command, returning the exit status. -}
|
-- | Runs a system command, returning the exit status.
|
||||||
safeSystem :: FilePath -> [CommandParam] -> IO ExitCode
|
safeSystem :: FilePath -> [CommandParam] -> IO ExitCode
|
||||||
safeSystem command params = safeSystem' command params id
|
safeSystem command params = safeSystem' command params id
|
||||||
|
|
||||||
|
@ -74,23 +74,22 @@ safeSystemEnv :: FilePath -> [CommandParam] -> Maybe [(String, String)] -> IO Ex
|
||||||
safeSystemEnv command params environ = safeSystem' command params $
|
safeSystemEnv command params environ = safeSystem' command params $
|
||||||
\p -> p { env = environ }
|
\p -> p { env = environ }
|
||||||
|
|
||||||
{- Wraps a shell command line inside sh -c, allowing it to be run in a
|
-- | Wraps a shell command line inside sh -c, allowing it to be run in a
|
||||||
- login shell that may not support POSIX shell, eg csh. -}
|
-- login shell that may not support POSIX shell, eg csh.
|
||||||
shellWrap :: String -> String
|
shellWrap :: String -> String
|
||||||
shellWrap cmdline = "sh -c " ++ shellEscape cmdline
|
shellWrap cmdline = "sh -c " ++ shellEscape cmdline
|
||||||
|
|
||||||
{- Escapes a filename or other parameter to be safely able to be exposed to
|
-- | Escapes a filename or other parameter to be safely able to be exposed to
|
||||||
- the shell.
|
-- the shell.
|
||||||
-
|
--
|
||||||
- This method works for POSIX shells, as well as other shells like csh.
|
-- This method works for POSIX shells, as well as other shells like csh.
|
||||||
-}
|
|
||||||
shellEscape :: String -> String
|
shellEscape :: String -> String
|
||||||
shellEscape f = "'" ++ escaped ++ "'"
|
shellEscape f = "'" ++ escaped ++ "'"
|
||||||
where
|
where
|
||||||
-- replace ' with '"'"'
|
-- replace ' with '"'"'
|
||||||
escaped = join "'\"'\"'" $ split "'" f
|
escaped = join "'\"'\"'" $ split "'" f
|
||||||
|
|
||||||
{- Unescapes a set of shellEscaped words or filenames. -}
|
-- | Unescapes a set of shellEscaped words or filenames.
|
||||||
shellUnEscape :: String -> [String]
|
shellUnEscape :: String -> [String]
|
||||||
shellUnEscape [] = []
|
shellUnEscape [] = []
|
||||||
shellUnEscape s = word : shellUnEscape rest
|
shellUnEscape s = word : shellUnEscape rest
|
||||||
|
@ -107,19 +106,19 @@ shellUnEscape s = word : shellUnEscape rest
|
||||||
| c == q = findword w cs
|
| c == q = findword w cs
|
||||||
| otherwise = inquote q (w++[c]) cs
|
| otherwise = inquote q (w++[c]) cs
|
||||||
|
|
||||||
{- For quickcheck. -}
|
-- | For quickcheck.
|
||||||
prop_idempotent_shellEscape :: String -> Bool
|
prop_idempotent_shellEscape :: String -> Bool
|
||||||
prop_idempotent_shellEscape s = [s] == (shellUnEscape . shellEscape) s
|
prop_idempotent_shellEscape s = [s] == (shellUnEscape . shellEscape) s
|
||||||
prop_idempotent_shellEscape_multiword :: [String] -> Bool
|
prop_idempotent_shellEscape_multiword :: [String] -> Bool
|
||||||
prop_idempotent_shellEscape_multiword s = s == (shellUnEscape . unwords . map shellEscape) s
|
prop_idempotent_shellEscape_multiword s = s == (shellUnEscape . unwords . map shellEscape) s
|
||||||
|
|
||||||
{- Segments a list of filenames into groups that are all below the maximum
|
-- | Segments a list of filenames into groups that are all below the maximum
|
||||||
- command-line length limit. -}
|
-- command-line length limit.
|
||||||
segmentXargsOrdered :: [FilePath] -> [[FilePath]]
|
segmentXargsOrdered :: [FilePath] -> [[FilePath]]
|
||||||
segmentXargsOrdered = reverse . map reverse . segmentXargsUnordered
|
segmentXargsOrdered = reverse . map reverse . segmentXargsUnordered
|
||||||
|
|
||||||
{- Not preserving data is a little faster, and streams better when
|
-- | Not preserving order is a little faster, and streams better when
|
||||||
- there are a great many filesnames. -}
|
-- there are a great many filenames.
|
||||||
segmentXargsUnordered :: [FilePath] -> [[FilePath]]
|
segmentXargsUnordered :: [FilePath] -> [[FilePath]]
|
||||||
segmentXargsUnordered l = go l [] 0 []
|
segmentXargsUnordered l = go l [] 0 []
|
||||||
where
|
where
|
||||||
|
|
Loading…
Reference in New Issue