On 2007-08-31, Andrea Rossato <[EMAIL PROTECTED]> wrote:
> On Fri, Aug 31, 2007 at 12:23:42AM +0000, Aaron Denney wrote:
>> On 2007-08-30, Andrea Rossato <[EMAIL PROTECTED]> wrote:
>> > Hi,
>> >
>> > there's something I don't get about interaction among OS processes and
>> > Haskell handles/channels.
>> 
>> This looks like a buffering problem.  You might be able to make it work by
>> explicitly setting "line buffering" with hSetBuffering
>
> Thanks for your kind attention, but I don't think it's a matter of
> buffering (I indeed tried playing with hSetBuffering with no results).

I'd like to convince you otherwise:

changing main1 to 
main = do
  (i,o,e,p) <- runInteractiveCommand "./main2"
  hSetBuffering i LineBuffering
  hSetBuffering o LineBuffering
  loop (i,o,e,p)

loop c@(i,o,e,p) = do
  s <- getLine
  hPutStrLn i s
  hFlush i -- now "i" is closed, right?
  s' <- hGetLine o
  putStrLn s'
  loop c

and main2 to
import System.IO

main = do
  hSetBuffering stdin LineBuffering
  hSetBuffering stdout LineBuffering
  s <- getLine
  case s of
    "quit" -> putStrLn "quitting" >> return ()
    _ -> loop s
  where
    loop s = do
         putStrLn s
         main

seems to work for me.

If you want "expect" like functionality, i.e. working for arbitrary
client programs, you'll need to use pseudottys, as expect, script,
screen, xterm, etc. do.  Unfortunately, the exact details of how to
do this vary from unix to unix, and as far as I know, have not been
packaged up nicely as a Haskell library.  You will have to use the FFI.

-- 
Aaron Denney
-><-

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

Reply via email to