(with apologies to D. Adams)

Hi, 

The code enclosed, works as expected for 2.10, works for
proto-3.03-15-Jul but breaks for 3.03 (latest from the CVS). The
problems seems to be something to do with handles: you write something
to it, but it doesn't go to the pipe.

With the code I am working right now (the SQL thingy) the problem
shows up as non-termination, while it happily terminates under proto. 

Feel free to get back to me if you want to see the real code, but the
enclosed demonstrates that there is something wrong.

Thanks, 

Laszlo & Liuhai


--------------------------------------------------------------------
module Main(main) where

import IO
import Posix
import System

main = do
        a <- echoIt "aaa"
        putStrLn a
       where
        aaa = "aaa" : aaa
        echoIt x = do
                     (inH, outH) <- exec "/bin/cat" []
                     hPutStr inH x
                     fd <- handleToFd inH
                     fdClose fd
                     x <- hGetContents outH
                     return x
                        

exec :: String -> [String] -> IO (Handle, Handle)
exec cmd args = do
  (pWriteFd, cReadFd) <- createPipe
  (cWriteFd, pReadFd) <- createPipe
  child             <- forkProcess
  case child of
   Just x  -> do -- parent
     pWriteH <- fdToHandle pWriteFd
     pReadH  <- fdToHandle pReadFd
     fdClose cReadFd
     fdClose cWriteFd
     hSetBuffering pWriteH NoBuffering
     hSetBuffering pReadH  NoBuffering
     return (pWriteH, pReadH)
   Nothing -> do -- child
     -- replace stdin, stdout with read and write end of the pipe.
     dupTo cReadFd  stdInput
     dupTo cWriteFd stdOutput
     fdClose pReadFd
     fdClose pWriteFd
     executeFile cmd True args Nothing
     exitWith ExitSuccess

Reply via email to