{-# LANGUAGE CPP #-}
module System.Cmd.Utils(
PipeHandle(..),
safeSystem,
#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__))
forceSuccess,
#ifndef __HUGS__
posixRawSystem,
forkRawSystem,
pipeFrom,
pipeLinesFrom,
pipeTo,
pipeBoth,
hPipeFrom,
hPipeTo,
hPipeBoth,
#endif
#endif
PipeMode(..),
#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__))
#ifndef __HUGS__
pOpen, pOpen3, pOpen3Raw
#endif
#endif
)
where
import System.Exit
import System.Process (rawSystem)
import System.Log.Logger
#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__))
import System.Posix.IO
import System.Posix.Process
import System.Posix.Signals
import qualified System.Posix.Signals
#endif
import System.Posix.Types
import System.IO
import System.IO.Error
import Control.Concurrent(forkIO)
import Control.Exception(finally)
import qualified Control.Exception(try, IOException)
data PipeMode = ReadFromPipe | WriteToPipe
logbase :: String
logbase = "System.Cmd.Utils"
data PipeHandle =
PipeHandle { processID :: ProcessID,
phCommand :: FilePath,
phArgs :: [String],
phCreator :: String
}
deriving (Eq, Show)
#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__))
#ifndef __HUGS__
pipeLinesFrom :: FilePath -> [String] -> IO (PipeHandle, [String])
pipeLinesFrom fp args =
do (pid, c) <- pipeFrom fp args
return $ (pid, lines c)
#endif
#endif
logRunning :: String -> FilePath -> [String] -> IO ()
logRunning func fp args = debugM (logbase ++ "." ++ func) (showCmd fp args)
warnFail :: [Char] -> FilePath -> [String] -> [Char] -> IO t
warnFail funcname fp args msg =
let m = showCmd fp args ++ ": " ++ msg
in do warningM (logbase ++ "." ++ funcname) m
fail m
#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__))
#ifndef __HUGS__
hPipeFrom :: FilePath -> [String] -> IO (PipeHandle, Handle)
hPipeFrom fp args =
do pipepair <- createPipe
logRunning "pipeFrom" fp args
let childstuff = do dupTo (snd pipepair) stdOutput
closeFd (fst pipepair)
executeFile fp True args Nothing
p <- Control.Exception.try (forkProcess childstuff)
pid <- case p of
Right x -> return x
Left (e :: Control.Exception.IOException) -> warnFail "pipeFrom" fp args $
"Error in fork: " ++ show e
closeFd (snd pipepair)
h <- fdToHandle (fst pipepair)
return (PipeHandle pid fp args "pipeFrom", h)
#endif
#endif
#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__))
#ifndef __HUGS__
pipeFrom :: FilePath -> [String] -> IO (PipeHandle, String)
pipeFrom fp args =
do (pid, h) <- hPipeFrom fp args
c <- hGetContents h
return (pid, c)
#endif
#endif
#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__))
#ifndef __HUGS__
hPipeTo :: FilePath -> [String] -> IO (PipeHandle, Handle)
hPipeTo fp args =
do pipepair <- createPipe
logRunning "pipeTo" fp args
let childstuff = do dupTo (fst pipepair) stdInput
closeFd (snd pipepair)
executeFile fp True args Nothing
p <- Control.Exception.try (forkProcess childstuff)
pid <- case p of
Right x -> return x
Left (e :: Control.Exception.IOException) -> warnFail "pipeTo" fp args $
"Error in fork: " ++ show e
closeFd (fst pipepair)
h <- fdToHandle (snd pipepair)
return (PipeHandle pid fp args "pipeTo", h)
#endif
#endif
#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__))
#ifndef __HUGS__
pipeTo :: FilePath -> [String] -> String -> IO PipeHandle
pipeTo fp args message =
do (pid, h) <- hPipeTo fp args
finally (hPutStr h message)
(hClose h)
return pid
#endif
#endif
#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__))
#ifndef __HUGS__
hPipeBoth :: FilePath -> [String] -> IO (PipeHandle, Handle, Handle)
hPipeBoth fp args =
do frompair <- createPipe
topair <- createPipe
logRunning "pipeBoth" fp args
let childstuff = do dupTo (snd frompair) stdOutput
closeFd (fst frompair)
dupTo (fst topair) stdInput
closeFd (snd topair)
executeFile fp True args Nothing
p <- Control.Exception.try (forkProcess childstuff)
pid <- case p of
Right x -> return x
Left (e :: Control.Exception.IOException) -> warnFail "pipeBoth" fp args $
"Error in fork: " ++ show e
closeFd (snd frompair)
closeFd (fst topair)
fromh <- fdToHandle (fst frompair)
toh <- fdToHandle (snd topair)
return (PipeHandle pid fp args "pipeBoth", fromh, toh)
#endif
#endif
#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__))
#ifndef __HUGS__
pipeBoth :: FilePath -> [String] -> String -> IO (PipeHandle, String)
pipeBoth fp args message =
do (pid, fromh, toh) <- hPipeBoth fp args
forkIO $ finally (hPutStr toh message)
(hClose toh)
c <- hGetContents fromh
return (pid, c)
#endif
#endif
#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__))
forceSuccess :: PipeHandle -> IO ()
forceSuccess (PipeHandle pid fp args funcname) =
let warnfail = warnFail funcname
in do status <- getProcessStatus True False pid
case status of
Nothing -> warnfail fp args $ "Got no process status"
Just (Exited (ExitSuccess)) -> return ()
Just (Exited (ExitFailure fc)) ->
cmdfailed funcname fp args fc
#if MIN_VERSION_unix(2,7,0)
Just (Terminated sig _) ->
#else
Just (Terminated sig) ->
#endif
warnfail fp args $ "Terminated by signal " ++ show sig
Just (Stopped sig) ->
warnfail fp args $ "Stopped by signal " ++ show sig
#endif
safeSystem :: FilePath -> [String] -> IO ()
safeSystem command args =
do debugM (logbase ++ ".safeSystem")
("Running: " ++ command ++ " " ++ (show args))
#if defined(__HUGS__) || defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__)
ec <- rawSystem command args
case ec of
ExitSuccess -> return ()
ExitFailure fc -> cmdfailed "safeSystem" command args fc
#else
ec <- posixRawSystem command args
case ec of
Exited ExitSuccess -> return ()
Exited (ExitFailure fc) -> cmdfailed "safeSystem" command args fc
#if MIN_VERSION_unix(2,7,0)
Terminated s _ -> cmdsignalled "safeSystem" command args s
#else
Terminated s -> cmdsignalled "safeSystem" command args s
#endif
Stopped s -> cmdsignalled "safeSystem" command args s
#endif
#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__))
#ifndef __HUGS__
posixRawSystem :: FilePath -> [String] -> IO ProcessStatus
posixRawSystem program args =
do debugM (logbase ++ ".posixRawSystem")
("Running: " ++ program ++ " " ++ (show args))
oldint <- installHandler sigINT Ignore Nothing
oldquit <- installHandler sigQUIT Ignore Nothing
let sigset = addSignal sigCHLD emptySignalSet
oldset <- getSignalMask
blockSignals sigset
childpid <- forkProcess (childaction oldint oldquit oldset)
mps <- getProcessStatus True False childpid
restoresignals oldint oldquit oldset
let retval = case mps of
Just x -> x
Nothing -> error "Nothing returned from getProcessStatus"
debugM (logbase ++ ".posixRawSystem")
(program ++ ": exited with " ++ show retval)
return retval
where childaction oldint oldquit oldset =
do restoresignals oldint oldquit oldset
executeFile program True args Nothing
restoresignals oldint oldquit oldset =
do installHandler sigINT oldint Nothing
installHandler sigQUIT oldquit Nothing
setSignalMask oldset
#endif
#endif
#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__))
#ifndef __HUGS__
forkRawSystem :: FilePath -> [String] -> IO ProcessID
forkRawSystem program args =
do debugM (logbase ++ ".forkRawSystem")
("Running: " ++ program ++ " " ++ (show args))
forkProcess childaction
where
childaction = executeFile program True args Nothing
#endif
#endif
cmdfailed :: String -> FilePath -> [String] -> Int -> IO a
cmdfailed funcname command args failcode = do
let errormsg = "Command " ++ command ++ " " ++ (show args) ++
" failed; exit code " ++ (show failcode)
let e = userError (errormsg)
warningM (logbase ++ "." ++ funcname) errormsg
ioError e
#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__))
#ifndef __HUGS__
cmdsignalled :: String -> FilePath -> [String] -> Signal -> IO a
cmdsignalled funcname command args failcode = do
let errormsg = "Command " ++ command ++ " " ++ (show args) ++
" failed due to signal " ++ (show failcode)
let e = userError (errormsg)
warningM (logbase ++ "." ++ funcname) errormsg
ioError e
#endif
#endif
#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__))
#ifndef __HUGS__
pOpen :: PipeMode -> FilePath -> [String] ->
(Handle -> IO a) -> IO a
pOpen pm fp args func =
do
pipepair <- createPipe
debugM (logbase ++ ".pOpen")
("Running: " ++ fp ++ " " ++ (show args))
case pm of
ReadFromPipe -> do
let callfunc _ = do
closeFd (snd pipepair)
h <- fdToHandle (fst pipepair)
x <- func h
hClose h
return $! x
pOpen3 Nothing (Just (snd pipepair)) Nothing fp args
callfunc (closeFd (fst pipepair))
WriteToPipe -> do
let callfunc _ = do
closeFd (fst pipepair)
h <- fdToHandle (snd pipepair)
x <- func h
hClose h
return $! x
pOpen3 (Just (fst pipepair)) Nothing Nothing fp args
callfunc (closeFd (snd pipepair))
#endif
#endif
#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__))
#ifndef __HUGS__
pOpen3 :: Maybe Fd
-> Maybe Fd
-> Maybe Fd
-> FilePath
-> [String]
-> (ProcessID -> IO a)
-> IO ()
-> IO a
pOpen3 pin pout perr fp args func childfunc =
do pid <- pOpen3Raw pin pout perr fp args childfunc
retval <- func $! pid
let rv = seq retval retval
forceSuccess (PipeHandle (seq retval pid) fp args "pOpen3")
return rv
#endif
#endif
#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__))
#ifndef __HUGS__
pOpen3Raw :: Maybe Fd
-> Maybe Fd
-> Maybe Fd
-> FilePath
-> [String]
-> IO ()
-> IO ProcessID
pOpen3Raw pin pout perr fp args childfunc =
let mayberedir Nothing _ = return ()
mayberedir (Just fromfd) tofd = do
dupTo fromfd tofd
closeFd fromfd
return ()
childstuff = do
mayberedir pin stdInput
mayberedir pout stdOutput
mayberedir perr stdError
childfunc
debugM (logbase ++ ".pOpen3")
("Running: " ++ fp ++ " " ++ (show args))
executeFile fp True args Nothing
in
do
p <- Control.Exception.try (forkProcess childstuff)
pid <- case p of
Right x -> return x
Left (e :: Control.Exception.IOException) -> fail ("Error in fork: " ++ (show e))
return pid
#endif
#endif
showCmd :: FilePath -> [String] -> String
showCmd fp args = fp ++ " " ++ show args