Bugs item #1249226, was opened at 2005-07-31 21:28
Message generated for change (Comment added) made by nobody
You can respond by visiting: 
https://sourceforge.net/tracker/?func=detail&atid=108032&aid=1249226&group_id=8032

Please note that this message will contain a full copy of the comment thread,
including the initial issue submission, for this request,
not just the latest update.
Category: libraries/base
Group: None
Status: Closed
Resolution: Fixed
Priority: 5
Submitted By: Nobody/Anonymous (nobody)
Assigned to: Nobody/Anonymous (nobody)
Summary: runInteractiveProcess and closed stdin.

Initial Comment:
Hello,

The System.Process.runInteractiveProcess function
doesn't seem to provide the child process with a stdin
handle when the parent's stdin is closed. Below is a
small example:

import System.Process
import Control.Concurrent
import System.IO

main = do
  hClose stdin -- everything works as expected if the
handle isn't closed.
  putStrLn "Running cat ..."
  (inp, out, err, pid) <- runInteractiveProcess "cat"
[] Nothing Nothing
  forkIO (hPutStrLn inp "foo" >> hClose inp)
  forkIO (putStrLn =<< hGetContents out)
  forkIO (putStrLn =<< hGetContents err)
  -- Don't want to deal with waitForProcess and
-threaded right now.
  threadDelay 1000000
  return ()

Running this example produces the error

% ghc Run.hs -o run
% ./run
Running cat ...

cat: -: Bad file descriptor
cat: closing standard input: Bad file descriptor


I think the bug is in
fptools/libraries/base/cbits/runProcess.c:
//...
    pipe(fdStdInput);
//...
        dup2 (fdStdInput[0], STDIN_FILENO);
/...    
        close(fdStdInput[0]);
//...

pipe(...) will assign the lowest available file
descriptors, i.e. 0 if stdin is closed. The dup2 won't
do anything, since src and dest fds are identical, so
close(...) will close the child's stdin immediately.


% uname -a
Linux mthomas 2.6.12 #2 Thu Jul 21 07:51:44 EDT 2005
i686 GNU/Linux
% ghc --version
The Glorious Glasgow Haskell Compilation System,
version 6.5.20050728

Thanks,

-- Thomas Jäger

----------------------------------------------------------------------

Comment By: Nobody/Anonymous (nobody)
Date: 2005-08-01 20:28

Message:
Logged In: NO 

Simon,

Thanks, that fixes the bug for the most important case,
stdin, and therefore hs-plugin's runplugs. Unfortunately, it
doesn't cover all possible cases as the attached file shows:

% for i in `seq 0 7`; do ./run $i && echo 'succeeded' ||
echo 'failed!'; done
Closing handles: 
succeeded
Closing handles: stderr
succeeded
Closing handles: stdout
succeeded
Closing handles: stdout,stderr
failed!
Closing handles: stdin
succeeded
Closing handles: stdin,stderr
failed!
Closing handles: stdin,stdout
failed!
Closing handles: stdin,stdout,stderr
failed!

I can't really think of an easy way to solve this, since
pipe() isn't able to only use fds greater than a certain
number. My only idea is to copy the fds that are smaller
than 3 and that pipe() didn't get right, and then dup2()
them down to 0, 1 or 2 again.

Thomas

This is the attachment, for some reason I can't log into
soureforge right now.
-------
import System.Environment
import System.Process
import System.IO
import Control.Concurrent
import Control.Exception
import Control.Monad
import Data.List
import System.Exit

handles :: [(String,Handle)]
handles = [("stdin",stdin),("stdout",stdout),("stderr",stderr)]

main :: IO ()
main = do
  [n] <- getArgs
  let hs = filterM (\_ -> [False,True]) handles !! read n
  putStrLn $ "Closing handles: " ++ concat (intersperse ","
$ map fst hs)
  mapM_ (hClose . snd) hs
  threadDelay 10000

  outMVar <- newEmptyMVar
  errMVar <- newEmptyMVar
  (inp, out, err, _pid) <- 
    runInteractiveProcess "tee" ["-a","/dev/stderr"] Nothing
Nothing
  forkIO $ hPutStrLn inp "foo" >> hClose inp
  forkIO $ putMVar outMVar =<< evaluate =<< hGetContents out
  forkIO $ putMVar errMVar =<< evaluate =<< hGetContents err
  output <- readMVar outMVar
  errput <- readMVar errMVar
  unless (any (\xs -> "foo" `isPrefixOf` xs) (tails output))
$ exitFailure
  unless (any (\xs -> "foo" `isPrefixOf` xs) (tails errput))
$ exitFailure
  exitWith ExitSuccess


----------------------------------------------------------------------

Comment By: Simon Marlow (simonmar)
Date: 2005-08-01 06:24

Message:
Logged In: YES 
user_id=48280

Thanks, excellent report.  I've fixed the bug and added your
test program to the test suite.

----------------------------------------------------------------------

You can respond by visiting: 
https://sourceforge.net/tracker/?func=detail&atid=108032&aid=1249226&group_id=8032
_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to