aboutsummaryrefslogtreecommitdiff
path: root/Utility/SafeCommand.hs
diff options
context:
space:
mode:
authorGravatar Joey Hess <joey@kitenet.net>2011-08-22 16:14:12 -0400
committerGravatar Joey Hess <joey@kitenet.net>2011-08-22 16:14:12 -0400
commit203148363f459635b1be40b8c6ed376073230dda (patch)
tree422df5684fc77663c6a3c7fd601c1eff27b3758b /Utility/SafeCommand.hs
parent4c73d77b42e97ad740d5731ad73c40a31c0c84f9 (diff)
split groups of related functions out of Utility
Diffstat (limited to 'Utility/SafeCommand.hs')
-rw-r--r--Utility/SafeCommand.hs104
1 files changed, 104 insertions, 0 deletions
diff --git a/Utility/SafeCommand.hs b/Utility/SafeCommand.hs
new file mode 100644
index 000000000..ba9362603
--- /dev/null
+++ b/Utility/SafeCommand.hs
@@ -0,0 +1,104 @@
+{- safely running shell commands
+ -
+ - Copyright 2010-2011 Joey Hess <joey@kitenet.net>
+ -
+ - Licensed under the GNU GPL version 3 or higher.
+ -}
+
+module Utility.SafeCommand where
+
+import System.Exit
+import qualified System.Posix.Process
+import System.Posix.Process hiding (executeFile)
+import System.Posix.Signals
+import Data.String.Utils
+import System.Log.Logger
+
+{- A type for parameters passed to a shell command. A command can
+ - be passed either some Params (multiple parameters can be included,
+ - whitespace-separated, or a single Param (for when parameters contain
+ - whitespace), or a File.
+ -}
+data CommandParam = Params String | Param String | File FilePath
+ deriving (Eq, Show, Ord)
+
+{- Used to pass a list of CommandParams to a function that runs
+ - a command and expects Strings. -}
+toCommand :: [CommandParam] -> [String]
+toCommand = (>>= unwrap)
+ where
+ unwrap (Param s) = [s]
+ unwrap (Params s) = filter (not . null) (split " " s)
+ -- Files that start with a dash are modified to avoid
+ -- the command interpreting them as options.
+ unwrap (File s@('-':_)) = ["./" ++ s]
+ unwrap (File s) = [s]
+
+{- Run a system command, and returns True or False
+ - if it succeeded or failed.
+ -
+ - SIGINT(ctrl-c) is allowed to propigate and will terminate the program.
+ -}
+boolSystem :: FilePath -> [CommandParam] -> IO Bool
+boolSystem command params = boolSystemEnv command params Nothing
+
+boolSystemEnv :: FilePath -> [CommandParam] -> Maybe [(String, String)] -> IO Bool
+boolSystemEnv command params env = do
+ -- Going low-level because all the high-level system functions
+ -- block SIGINT etc. We need to block SIGCHLD, but allow
+ -- SIGINT to do its default program termination.
+ let sigset = addSignal sigCHLD emptySignalSet
+ oldint <- installHandler sigINT Default Nothing
+ oldset <- getSignalMask
+ blockSignals sigset
+ childpid <- forkProcess $ childaction oldint oldset
+ mps <- getProcessStatus True False childpid
+ restoresignals oldint oldset
+ case mps of
+ Just (Exited ExitSuccess) -> return True
+ _ -> return False
+ where
+ restoresignals oldint oldset = do
+ _ <- installHandler sigINT oldint Nothing
+ setSignalMask oldset
+ childaction oldint oldset = do
+ restoresignals oldint oldset
+ executeFile command True (toCommand params) env
+
+{- executeFile with debug logging -}
+executeFile :: FilePath -> Bool -> [String] -> Maybe [(String, String)] -> IO ()
+executeFile c path p e = do
+ debugM "Utility.SafeCommand.executeFile" $
+ "Running: " ++ c ++ " " ++ show p ++ " " ++ maybe "" show e
+ System.Posix.Process.executeFile c path p e
+
+{- Escapes a filename or other parameter to be safely able to be exposed to
+ - the shell. -}
+shellEscape :: String -> String
+shellEscape f = "'" ++ escaped ++ "'"
+ where
+ -- replace ' with '"'"'
+ escaped = join "'\"'\"'" $ split "'" f
+
+{- Unescapes a set of shellEscaped words or filenames. -}
+shellUnEscape :: String -> [String]
+shellUnEscape [] = []
+shellUnEscape s = word : shellUnEscape rest
+ where
+ (word, rest) = findword "" s
+ findword w [] = (w, "")
+ findword w (c:cs)
+ | c == ' ' = (w, cs)
+ | c == '\'' = inquote c w cs
+ | c == '"' = inquote c w cs
+ | otherwise = findword (w++[c]) cs
+ inquote _ w [] = (w, "")
+ inquote q w (c:cs)
+ | c == q = findword w cs
+ | otherwise = inquote q (w++[c]) cs
+
+{- For quickcheck. -}
+prop_idempotent_shellEscape :: String -> Bool
+prop_idempotent_shellEscape s = [s] == (shellUnEscape . shellEscape) s
+prop_idempotent_shellEscape_multiword :: [String] -> Bool
+prop_idempotent_shellEscape_multiword s = s == (shellUnEscape . unwords . map shellEscape) s