Higher level interface to System.Process
Donald Bruce Stewart
dons at cse.unsw.edu.au
Sat Dec 16 03:03:18 EST 2006
wferi:
> on my computer your code (with >> return ()-s inserted) works with at
> most 135168=132*1024 bytes of input:
>
> One more byte, and cat blocks on writing to its pipe. No wonder,
> nobody reads the other end, as our hPutStr to cat also blocks, as a
> direct consequence. Moving the case beyond the forkIO-s resolves
> this. Btw, why don't you close the other handles? Btw2 runCommand in
> http://happs.org/HAppS/src/HAppS/Util/Common.hs takes a similar
> approach with MVar-s; I wonder if they are really needed.
Ok, I really want to push forwards the effort to add a nice popen to
base. Here's my first effort at a minimal clean interface, that we
might be proud to demonstrate in a tutorial ;)
import System.Process.Run
main = do
edate <- readProcess "date" ["+%y-%m-%d"] []
case edate of
Left err -> print err
Right date -> putStr date
The code for readProcess is in darcs, here:
darcs get http://www.cse.unsw.edu.au/~dons/code/newpopen
I'd like some comments on this approach. Suggestions on where to
generalise this, and yet keep it clean and simple, and so on.
Thanks,
Don
The module itself is attached:
-----------------------------------------------------------------------------
-- |
-- Module : System.Process.Run
-- Copyright : (c) Don Stewart 2006
-- License : BSD-style (see the file libraries/base/LICENSE)
--
-- Maintainer : dons at cse.unsw.edu.au
-- Stability : experimental
-- Portability : currently non-portable (Control.Concurrent)
--
-- Convenient interface to external processes
--
module System.Process.Run (
-- * Running processes
readProcess
) where
import System.Process
import System.Exit
import System.IO
import Control.Monad
import Control.Concurrent
import qualified Control.Exception as C
--
-- | readProcess forks an external process, reads its standard output,
-- waits for the process to terminate, and returns either the output
-- string, or an exitcode.
--
readProcess :: FilePath -- ^ command to run
-> [String] -- ^ any arguments
-> String -- ^ standard input
-> IO (Either ExitCode String) -- ^ either the stdout, or an exitcode
readProcess cmd args input = C.handle (return . handler) $ do
(inh,outh,errh,pid) <- runInteractiveProcess cmd args Nothing Nothing
-- fork off a thread to start consuming the output
output <- hGetContents outh
outMVar <- newEmptyMVar
forkIO $ C.evaluate (length output) >> putMVar outMVar ()
-- now write and flush any input
when (not (null input)) $ hPutStr inh input
hClose inh -- done with stdin
hClose errh -- ignore stderr
-- wait on the output
takeMVar outMVar
hClose outh
-- wait on the process
ex <- C.catch (waitForProcess pid) (\_ -> return ExitSuccess)
return $ case ex of
ExitSuccess -> Right output
ExitFailure _ -> Left ex
where
handler (C.ExitException e) = Left e
handler e = Left (ExitFailure 1)
More information about the Libraries
mailing list