[Haskell-cafe] System.Process and -threaded

Donn Cave donn at avvanta.com
Sun May 18 16:14:39 UTC 2014


> Try forking a couple of threads to keep those handles clear.

Well ... at what point do these conveniences become too much work?

Quick outline of the problems we can expect to encounter if we use
runInteractiveProcess:

-- because of Handles for the pipe I/O --
1.  library buffering defaults are the opposite of useful
2.  now we find the depending on -threaded, garbage collection
    may cause handles to be closed
-- because all three standard units are redirected to pipes --
3.  handles are likely to be unused, contributing to problem 2 above
4.  unused handles are also liable to fill with process output and block.
5.  particularly with unit 2 ("stderr"), diagnostic output will be
    discarded unless copied to output by the parent process
6.  it's tricky to handle output on two units - have to avoid blocking
    read, if you don't know there's output.

... and I likely am forgetting one or two more.

My recommendation would be to never use this function, and instead
go to a process/pipe/exec that
1.  creates only the required pipe connections, usually one.
2.  returns the pipe Fd rather than making it into a Handle

I append an example implementation - a little crude inasmuch as
it does nothing about potential exceptional conditions like
exec failure.

	Donn
------------
module Spawn (spawnFd) where
import System.Directory
import System.Posix.IO
import System.Posix.Process
import System.Posix.Types

--
--  fork process, exec file
--
--  exec parameters same as executeFile
--
--  Fd spec is (unit, write) from the perspective of
--  the child process.
--    To spawn a process that only writes output, and
--    get a pipe to read that output: [(1, True)]
--    To spawn a process that only reads input: [(0, False)]
--    To get all three units like runInteractiveProcess:
--         [(0, False), (1, True), (2, True)]
--  Returned fds are not super convenient, something like
--    let p0 = fromJust $ lookup 0 pipelist
   
spawnFd :: FilePath -> Bool -> [String] -> Maybe FilePath
  -> Maybe [(String, String)] -> [(Fd, Bool)]
  -> IO ([(Fd, Fd)], ProcessID)
spawnFd path search args wd env fdreq = do
    pp <- mapM pipu fdreq
    pid <- forkProcess $ childPrep pp
    ppp <- mapM repipe pp
    return (ppp, pid)
    where
        pipu (u, w) = do
            p <- createPipe
            return (u, w, p)
        dopipe (u, w, (p0, p1)) = do
            if w
                then dupTo p1 u
                else dupTo p0 u
            closeFd p0
            closeFd p1
        repipe (u, w, (p0, p1))
            | w = do
                closeFd p1
                return (u, p0)
            | otherwise = do
                closeFd p0
                return (u, p1)
        childPrep pp = do
            mapM_ dopipe pp
            case wd of
                Just d -> setCurrentDirectory d
                _ -> return ()
            executeFile path search args env


More information about the Haskell-Cafe mailing list