System.Process and -threaded

Hello, I'm writing a little networking wrapper around a sub-process (mplayer -idle -slave) and I'm running into some issues with the System.Process API. This is the program:
module Main where
import System.IO import System.Process import Network.Socket hiding (recv) import Network.Socket.ByteString import Control.Concurrent import qualified Data.ByteString.Char8 as C
-- WARNING: when compiled with -threaded, this program is likely not going -- to work. As soon as one writes to the stdin of the forked process, it -- zombifies and any other command with crash this program.
main = withSocketsDo $ do -- network stuff addrinfos <- getAddrInfo Nothing (Just "localhost") (Just "4000") let serveraddr = head addrinfos sock <- socket (addrFamily serveraddr) Stream defaultProtocol bindSocket sock (addrAddress serveraddr) listen sock 1
-- mplayer (hand,o,e,pid) <- runInteractiveProcess "mplayer" ["-fs", "-idle", "-slave"] Nothing Nothing hSetBinaryMode hand False hSetBuffering hand LineBuffering
putStrLn "listening for commands" loop sock hand
-- closing everything down sClose sock terminateProcess pid waitForProcess pid return ()
loop sock hand = do (conn, _) <- accept sock str <- recv conn 2048
putStr $ "received: " ++ C.unpack str
-- write command to handler hPutStr hand $ C.unpack str
sClose conn loop sock hand
When compile with -threaded, the mplayer process gets zombified and hangs until I shut down the program. When compiled with non-threaded RTS (thats whats its called, correct?) I can successfully send a few commands, but then mplayer freezes. When I strace mplayer, this error is what it gets stuck on. ioctl(0, TIOCGWINSZ, 0x7fff2897a070) = -1 ENOTTY (Inappropriate ioctl for device) Apparently that means I'm trying to communicate with it as though it were a type writer. How fitting :) The commands are all simple strings as docs here: http://www.mplayerhq.hu/DOCS/tech/slave.txt My questions are these: is there anything I need to take care of when handling sub-processes like this, specifically while writing to stdin of the process, and with particular regard to -threaded? Does anybody spot a problem or something I'm overlooking when handling processes like this? I have been reading the API docs, but found no mention of potential caveats pertaining to -threaded. Thanks! k ✉ k@ioctl.it ☎ +49(0)176 / 61995110

quoth Karsten Gebbert, ...
My questions are these: is there anything I need to take care of when handling sub-processes like this, specifically while writing to stdin of the process, and with particular regard to -threaded? Does anybody spot a problem or something I'm overlooking when handling processes like this?
I can't say I know what's going wrong. One thing you can do when using handles on a pipe, is put "hFlush hand" after your "hPutStr hand" - that will clean up problems with buffering. Really a process level buffered I/O layer like this is very little help for your application, and adds various complexities. If you're interested, you might extract the process handles' POSIX file descriptors and use those - System.Posix.IO handleToFd, fdWrite, etc. - just as an experiment. I don't see how the problems you report really suggest that you have a buffering problem that would naturally be cured by this, though. The other generic red flag here, for -threaded, is that the threaded runtime uses POSIX signals to dispatch certain background functions. That creates a flood of signal handling interrupts that can disrupt library functions. To find out if that's a problem, you may turn that off, on the command line +RTS -V0 -RTS. Donn

quoth Karsten Gebbert, ...
-- mplayer (hand,o,e,pid) <- runInteractiveProcess "mplayer" ["-fs", "-idle", "-slave"] Nothing Nothing
...
putStrLn "listening for commands" loop sock hand
-- closing everything down sClose sock terminateProcess pid waitForProcess pid return ()
In an idle moment I wrote up a simplified test program, and found something interesting. When compiled with -threaded, the above code garbage-collects and finalizes "o" -- the child process' output. That tends to shorten the process life span. If I build without -threaded, or use "o" during or after the loop, no problem. Or if I build with -threaded but run with the -V0 flag, which I suppose would delay garbage collection. Donn

You're not reading from the stdout or stderr of the subprocess, so either
those handles get garbage collected and closed (as Donn pointed out), which
will probably cause mplayer to crash, or the stdout buffer of the mplayer
process will fill and further write()s to that file descriptor will block,
causing deadlock. Try forking a couple of threads to keep those handles
clear.
G
On Sat, May 17, 2014 at 1:44 AM, Karsten Gebbert
Hello,
I'm writing a little networking wrapper around a sub-process (mplayer -idle -slave) and I'm running into some issues with the System.Process API. This is the program:
module Main where
import System.IO import System.Process import Network.Socket hiding (recv) import Network.Socket.ByteString import Control.Concurrent import qualified Data.ByteString.Char8 as C
-- WARNING: when compiled with -threaded, this program is likely not going -- to work. As soon as one writes to the stdin of the forked process, it -- zombifies and any other command with crash this program.
main = withSocketsDo $ do -- network stuff addrinfos <- getAddrInfo Nothing (Just "localhost") (Just "4000") let serveraddr = head addrinfos sock <- socket (addrFamily serveraddr) Stream defaultProtocol bindSocket sock (addrAddress serveraddr) listen sock 1
-- mplayer (hand,o,e,pid) <- runInteractiveProcess "mplayer" ["-fs", "-idle", "-slave"] Nothing Nothing hSetBinaryMode hand False hSetBuffering hand LineBuffering
putStrLn "listening for commands" loop sock hand
-- closing everything down sClose sock terminateProcess pid waitForProcess pid return ()
loop sock hand = do (conn, _) <- accept sock str <- recv conn 2048
putStr $ "received: " ++ C.unpack str
-- write command to handler hPutStr hand $ C.unpack str
sClose conn loop sock hand
When compile with -threaded, the mplayer process gets zombified and hangs until I shut down the program. When compiled with non-threaded RTS (thats whats its called, correct?) I can successfully send a few commands, but then mplayer freezes. When I strace mplayer, this error is what it gets stuck on.
ioctl(0, TIOCGWINSZ, 0x7fff2897a070) = -1 ENOTTY (Inappropriate ioctl for device)
Apparently that means I'm trying to communicate with it as though it were a type writer. How fitting :)
The commands are all simple strings as docs here:
http://www.mplayerhq.hu/DOCS/tech/slave.txt
My questions are these: is there anything I need to take care of when handling sub-processes like this, specifically while writing to stdin of the process, and with particular regard to -threaded? Does anybody spot a problem or something I'm overlooking when handling processes like this? I have been reading the API docs, but found no mention of potential caveats pertaining to -threaded.
Thanks!
k
✉ k@ioctl.it ☎ +49(0)176 / 61995110 _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
--
Gregory Collins

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
participants (3)
-
Donn Cave
-
Gregory Collins
-
Karsten Gebbert