Re: [Haskell-cafe] runInteractiveCommand: program ends before writing or reading all the output

2008-05-16 Thread Duncan Coutts

On Thu, 2008-05-15 at 21:04 -0400, Olivier Boudry wrote:

 I tried to place a length text `seq` before the mapM_ writeExport to
 force the process output to be read but the result was even worst
 (only one line printed). Apparently withtout the `evaluate` function
 it causes more troubles than it solves.

Yes, you should prefer evaluate over seq (or return $!) in the IO monad
because you sometimes have to distinguish between the evaluation that
happens when you construct your IO actions, and the evaluation that
happens when you run your IO actions. The evaluate action does the
latter and its ordered with respect to the other IO actions.

Duncan

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] runInteractiveCommand: program ends before writing or reading all the output

2008-05-15 Thread Philip Weaver
2008/5/15 Olivier Boudry [EMAIL PROTECTED]:
 Hi all,

 It's the first time I use the runInteractiveCommand and I was probably
 bitten by laziness.

 When I run the following program and send its output to a file using ''
 redirection I get the full output of the called process. But if I run it in
 the console I get only half of the output. As console is slower than disk I
 assume the called process terminates before all data has been read from it
 or the main process terminates before data has been written to stdout. I
 thought using waitForProcess, closing called process output and flushing
 stdout would solve the problem but it doesn't.

 -- Compile with -threaded option
 module Main where

 import Control.Concurrent (forkIO)
 import System.Environment (getArgs)
 import System.FilePath (dropExtension, takeFileName)
 import System.IO (Handle, hClose, hFlush, hGetContents, stdout)
 import System.Process (runInteractiveCommand, waitForProcess)

 main :: IO ()
 main = do
   (file:_) - getArgs
   (_, out, _, pid) - runInteractiveCommand $ dumpbin /EXPORTS  ++ file
   forkIO (createDefFile file out)
   waitForProcess pid
   hClose out
   hFlush stdout

 createDefFile :: String - Handle - IO ()
 createDefFile file inp = do
   putStrLn $ LIBRARY  ++ (dropExtension . takeFileName) file ++ .dll
   putStrLn EXPORTS
   text - hGetContents inp
   mapM_ writeExport $ keepExports $ map words $ lines text
   where
 keepExports :: [[String]] - [String]
 keepExports = map head
   . filter (not . null)
   . takeWhile ([Summary]/=)
   . drop 1
   . dropWhile ([ordinal,name]/=)
 writeExport ('_':xs) = putStrLn xs
 writeExport xs = putStrLn xs

 Any idea regarding the cause of this problem?


I think I've encountered the same problem several times, and it was
because I was reading from the handle lazily, like this:

   (_, out, _, pid) - runInteractiveProcess ...
   str - hGetContents out
   waitForProcess pid

But I didn't use 'str' until after the process finishes.  My solution
was to use strict IO, usually by replacing String with a strict
ByteString.  I hear there is now a library that lets you do strict IO
with Strings

Hope this helps.

 Thanks,

 Olivier.


 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] runInteractiveCommand: program ends before writing or reading all the output

2008-05-15 Thread Ronald Guida
It looks like a simple race condition to me.  You are using
waitForProcess pid to wait for runInteractiveCommand to finish, but
you don't seem to have anything that waits for createDefFile to
finish.

 main :: IO ()
 main = do
   (file:_) - getArgs
   (_, out, _, pid) - runInteractiveCommand $ dumpbin /EXPORTS  ++ file
   forkIO (createDefFile file out)
   waitForProcess pid
   hClose out
   hFlush stdout
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] runInteractiveCommand: program ends before writing or reading all the output

2008-05-15 Thread Philip Weaver
On Thu, May 15, 2008 at 11:42 AM, Ronald Guida [EMAIL PROTECTED] wrote:
 It looks like a simple race condition to me.  You are using
 waitForProcess pid to wait for runInteractiveCommand to finish, but
 you don't seem to have anything that waits for createDefFile to
 finish.

Whoops, sorry, I didn't read the original post closely enough.
 main :: IO ()
 main = do
   (file:_) - getArgs
   (_, out, _, pid) - runInteractiveCommand $ dumpbin /EXPORTS  ++ file
   forkIO (createDefFile file out)
   waitForProcess pid
   hClose out
   hFlush stdout
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] runInteractiveCommand: program ends before writing or reading all the output

2008-05-15 Thread Olivier Boudry
On Thu, May 15, 2008 at 2:42 PM, Ronald Guida [EMAIL PROTECTED] wrote:

 It looks like a simple race condition to me.  You are using
 waitForProcess pid to wait for runInteractiveCommand to finish, but
 you don't seem to have anything that waits for createDefFile to
 finish.


Thanks Ronald,

As I could not find a function to wait on a ThreadId I used a MVar to
synchronize both threads.

   sync - newEmptyMVar
   forkIO (createDefFile sync file out)
   waitForProcess pid
   takeMVar sync

and at the end of the forked thread:

   putMVar sync ()

Is this normal or have I missed the `waitOnThreadId` function?

Thanks for all the comments received on this thread,

Olivier.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] runInteractiveCommand: program ends before writing or reading all the output

2008-05-15 Thread Bulat Ziganshin
Hello Olivier,

Thursday, May 15, 2008, 11:06:19 PM, you wrote:

 As I could not find a function to wait on a ThreadId I used a MVar to 
 synchronize both threads.

 Is this normal or have I missed the `waitOnThreadId` function?

yes, it's common idiom


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] runInteractiveCommand: program ends before writing or reading all the output

2008-05-15 Thread Duncan Coutts

On Thu, 2008-05-15 at 13:40 -0400, Olivier Boudry wrote:
 Hi all,
 
 It's the first time I use the runInteractiveCommand and I was probably
 bitten by laziness.

Yes. I think Philip diagnosed the problem correctly.

As an example let me show you as an example how we use it in Cabal:

rawSystemStdout :: Verbosity - FilePath - [String] - IO String
rawSystemStdout verbosity path args = do
  Exception.bracket
 (runInteractiveProcess path args Nothing Nothing)
 (\(inh,outh,errh,_) - hClose inh  hClose outh  hClose errh)
$ \(_,outh,errh,pid) - do

  -- We want to process the output as text.
  hSetBinaryMode outh False

  -- fork off a thread to pull on (and discard) the stderr
  -- so if the process writes to stderr we do not block.
  -- NB. do the hGetContents synchronously, otherwise the outer
  -- bracket can exit before this thread has run, and hGetContents
  -- will fail.
  err - hGetContents errh 
  forkIO $ do evaluate (length err); return ()

  -- wait for all the output
  output - hGetContents outh
  evaluate (length output)

  -- wait for the program to terminate
  exitcode - waitForProcess pid

  -- on failure, throw the exit code as an exception  
  unless (exitCode == ExitSuccess) $ exitWith exitCode

  return (output, exitcode)


So as you can see there are two subtleties. One is the issue that we
have to make sure we get all the output before we wait for the program
to finish. Using evaluate is the trick there.

The other is that we also have to pull on the stderr of the process.
Otherwise the process may be trying to output to stderr but if the pipe
buffer fills up then writing to stderr will block and so it will not be
able to continue writing to stdout we'll have deadlocked the process. So
we have to forkIO a thread to pull on stderr.

This is one reason that runInteractiveProcess is hard to use and
especially hard to use portably due to the use of preemptable threads.
It would be possible to do without threads if we used non-blocking IO
and interleaved between reading from stdout and stderr.

Duncan

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] runInteractiveCommand: program ends before writing or reading all the output

2008-05-15 Thread Olivier Boudry
On Thu, May 15, 2008 at 6:23 PM, Duncan Coutts [EMAIL PROTECTED]
wrote:


 On Thu, 2008-05-15 at 13:40 -0400, Olivier Boudry wrote:
 As an example let me show you as an example how we use it in Cabal:


Hi Duncan,

I tried to place a length text `seq` before the mapM_ writeExport to force
the process output to be read but the result was even worst (only one line
printed). Apparently withtout the `evaluate` function it causes more
troubles than it solves.

The example you provided is really helpful. I learned a lot reading it.

Thanks,

Olivier.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe