Proposal: overhaul System.Process
Don Stewart
dons at galois.com
Tue Apr 22 18:52:17 EDT 2008
duncan.coutts:
>
> On Tue, 2008-04-22 at 15:35 -0700, Bryan O'Sullivan wrote:
> > Neil Mitchell wrote:
> >
> > > I would have thought (ExitCode,String) was more appropriate.
> >
> > Yes, definitely.
>
> Yes, I mentioned this to Don previously when he published his popen
> code. I think he agreed.
>
> Duncan
I'd changed, but not pushed out, process-light:
--
-- | readProcess forks an external process, reads its standard output
-- strictly, blocking until the process terminates, and returns either the output
-- string, or, in the case of non-zero exit status, an error code, and
-- any output.
--
-- Output is returned strictly, so this is not suitable for
-- interactive applications.
--
-- Users of this library should compile with -threaded if they
-- want other Haskell threads to keep running while waiting on
-- the result of readProcess.
--
-- > > readProcess "date" [] []
-- > Right "Thu Feb 7 10:03:39 PST 2008\n"
--
-- The argumenst are:
--
-- * The command to run, which must be in the $PATH, or an absolute path
--
-- * A list of separate command line arguments to the program
--
-- * A string to pass on the standard input to the program.
--
readProcess :: FilePath -- ^ command to run
-> [String] -- ^ any arguments
-> String -- ^ standard input
-> IO (Either (ExitCode,String) String) -- ^ either the stdout, or an exitcode and any output
readProcess cmd args input = C.handle (return . handler) $ do
(inh,outh,errh,pid) <- runInteractiveProcess cmd args Nothing Nothing
output <- hGetContents outh
outMVar <- newEmptyMVar
forkIO $ (C.evaluate (length output) >> putMVar outMVar ())
when (not (null input)) $ hPutStr inh input
takeMVar outMVar
ex <- C.catch (waitForProcess pid) (\_e -> return ExitSuccess)
hClose outh
hClose inh -- done with stdin
hClose errh -- ignore stderr
return $ case ex of
ExitSuccess -> Right output
ExitFailure _ -> Left (ex, output)
where
handler (C.ExitException e) = Left (e,"")
handler e = Left (ExitFailure 1, show e)
More information about the Libraries
mailing list