System.Process

Glynn Clements glynn.clements at virgin.net
Thu Jul 8 06:44:19 EDT 2004


Glynn Clements wrote:

> > I have tried to use the various POpen-like implementations
> > out there, but _none_ of them works with the most current
> > GHC. Is there any way to communicate with external programs
> > at the moment? Posix-only would be suffice at the moment.
> 
> There's the DIY solution, i.e. a direct translation of how popen() is
> implemented in C, e.g.:
> 
> > module Main where
> > 
> > import IO
> > import System
> > import System.Posix
> > 
> > main = do
> > 	(rfd, wfd) <- createPipe
> > 	pid <- forkProcess (proc rfd wfd)
> > 	closeFd wfd
> > 	hRead <- fdToHandle rfd
> > 	str <- hGetContents hRead
> > 	putStr str
> > 	stat <- getProcessStatus True False pid
> > 	case stat of
> > 		(Just (Exited code)) -> exitWith code
> > 		_ -> exitWith (ExitFailure 127)
> > 	where proc rfd wfd = do
> > 		closeFd rfd
> > 		dupTo wfd stdOutput
> > 		executeFile "/bin/ls" False ["-l"] Nothing
> 
> The above has been (briefly) tested with ghc 6.2.1.

I had forgotten about Simon's System.Process module (at the time of
the announcement, I was still on GHC 5.04.2, so I couldn't test it).

Here's a version of the above code which uses runProcess:

> module Main where
> 
> import IO ( hGetContents , hClose )
> import System ( exitWith )
> import System.Process ( runProcess , waitForProcess )
> import System.Posix ( createPipe , fdToHandle )
> 
> main = do
> 	(rfd, wfd) <- createPipe
> 	hRead <- fdToHandle rfd
> 	hWrite <- fdToHandle wfd
> 	handle <- runProcess "/bin/ls" ["-l"] Nothing Nothing (Just hWrite) Nothing
> 	hClose hWrite
> 	str <- hGetContents hRead
> 	putStr str
> 	code <- waitForProcess handle
> 	exitWith code

And another version which uses runInteractiveProcess:

> module Main where
> 
> import IO ( hGetContents )
> import System ( exitWith )
> import System.Process ( runInteractiveProcess , waitForProcess )
> 
> main = do
> 	(_, hOut, _, handle) <- runInteractiveProcess "/bin/ls" ["-l"] Nothing
> 	str <- hGetContents hOut
> 	putStr str
> 	code <- waitForProcess handle
> 	exitWith code

This last one isn't quite the same as popen(), as it automatically
associates each of the three standard descriptors with their own pipe,
whereas popen() only redirects one of stdin or stdout, while the other
one and stderr are inherited from the caller.

-- 
Glynn Clements <glynn.clements at virgin.net>


More information about the Libraries mailing list