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