piping with System.Process.createProcess
Claude Heiland-Allen
claudiusmaximus at goto10.org
Mon Jan 5 01:19:08 EST 2009
Greetings,
I think I found a bug in the process package.
GNU/Linux Debian Lenny
ghc-6.8.2
process-1.0.1.1
The short version:
UseHandle fails for input streams (subprocess can't read from it).
The long version:
> import System.Process
> import System.IO (Handle, hGetLine, hPutStrLn, hIsEOF, hClose)
> import System.Environment (getArgs)
> import Control.Concurrent (forkIO, threadDelay)
> import Control.Monad (forever, unless)
Forward
-------
A pipeline of processes defined in the "forwards" direction (where the
next process's input handle is the previous process's output handle).
> pipeForwards :: IO (Handle, Handle)
> pipeForwards = do
> (Just input, Just pipe, _, _) <- createProcess (proc "cat" []){
std_in = CreatePipe, std_out = CreatePipe }
> (_, Just output, _, _) <- createProcess (proc "cat" []){
std_in = UseHandle pipe, std_out = CreatePipe }
> return (input, output)
Data would flow through this pipe from top to bottom, which I find to
be intuitive. However, pipeForwards is broken; it fails with the
message "cat: -: Resource temporarily unavailable". (The "cat" that
fails is the "cat" with the UseHandle.)
Backward
--------
A pipeline of processes defined in the "backwards" direction (where the
next process's output handle is the previous process's input handle).
Data flows through this pipe from bottom to top, which I find to be
more confusing. But at least it works.
> pipeBackwards :: IO (Handle, Handle)
> pipeBackwards = do
> (Just pipe, Just output, _, _) <- createProcess (proc "cat" []){
std_in = CreatePipe, std_out = CreatePipe }
> (Just input, _, _, _) <- createProcess (proc "cat" []){
std_in = CreatePipe, std_out = UseHandle pipe }
> return (input, output)
Scaffold
--------
The main program pipes some data through one of the pipelines, depending
on the command line arguments.
> main :: IO ()
> main = do
> args <- getArgs
> (input, output) <- if null args then pipeForwards else pipeBackwards
> forkIO $ reader output
> forkIO $ writer input
> mainLoop
The reader thread will read all the lines from a handle and print them out.
> whileNotM :: Monad m => m Bool -> m a -> m ()
> whileNotM t a = t >>= \b -> unless b $ a >> whileNotM t a
> reader :: Handle -> IO ()
> reader h = whileNotM (hIsEOF h) (hGetLine h >>= putStrLn)
The writer thread will write some lines to a handle and then close it.
> writer :: Handle -> IO ()
> writer h = mapM_ (hPutStrLn h . replicate 10) ['a'..'z'] >> hClose h
The main thread will do nothing, so far as can be observed, and exists
solely to avoid premature termination of the program.
> mainLoop :: IO ()
> mainLoop = forever $ threadDelay 1000000
Thanks for your attention,
Claude
--
http://claudiusmaximus.goto10.org
More information about the Libraries
mailing list