[Haskell-beginners] merge two handles
Manfred Lotz
manfred.lotz at arcor.de
Wed Jun 15 15:23:03 CEST 2011
On Tue, 14 Jun 2011 13:10:36 -0400
David McBride <dmcbride at neondsl.com> wrote:
> It probably has to do more with parenthesis than anything:
>
> forever $ atomically $ readTchan chan >>= print
> forever $ (atomically $ readTchan chan) >>= print
>
> That might work. Once you get the types to line up, that should work.
>
Thanks for the hint. I finally got it compiled and almost working.
The code is now like this:
{-# LANGUAGE ScopedTypeVariables #-}
import GHC.Conc.Sync
import System.IO
import System.Environment
import System.Process
import Control.Monad
import Control.Concurrent.STM.TChan
import Control.Exception.Base
import Text.Printf
import Prelude hiding (catch)
makeThread :: Handle -> TChan String -> IO ThreadId
makeThread handle chan = forkIO $
forever
(do eof <- hIsEOF handle
unless eof $ hGetLine handle >>= atomically . writeTChan chan)
`catch` (\(e :: SomeException) -> return ())
issueCmd :: String -> [String] -> IO ()
issueCmd cmd parms = do
(_ ,Just hout ,Just herr ,_) <- createProcess (proc cmd parms) {
std_out = CreatePipe,
std_err = CreatePipe
}
chan <- newTChanIO :: IO (TChan String)
_ <- makeThread hout chan
_ <- makeThread herr chan
forever $ atomically (readTChan chan) >>= printf "%s\n"
main :: IO ()
main = do
args <- getArgs
let cmd = head args
let parms = tail args
issueCmd cmd parms
print "Done"
If I run this with a command the command's output will be printed but
after that the program is hanging, and top shows 100% cpu usage. "Done"
will never be printed.
Any idea what I have to add to prevent it from hanging?
--
Thanks,
Manfred
More information about the Beginners
mailing list