
Hi all, I have two handles where I get stdout resp. stderr from a command output. Is it possible to merge those two handles so that I get a new input handle in a way that data can be read from the new handle whenever it is available from either of the two original handles? -- Manfred

On Mon, Jun 13, 2011 at 12:35 PM, Manfred Lotz
Hi all, I have two handles where I get stdout resp. stderr from a command output.
Is it possible to merge those two handles so that I get a new input handle in a way that data can be read from the new handle whenever it is available from either of the two original handles?
Does what you're doing strictly need to be a handle? One thing you could try is is using an IO Channel: http://hackage.haskell.org/packages/archive/base/latest/doc/html/Control-Con... You can create the channel, then fork off two threads to pump messages from the handles into the channel, and then read the channel from your main thread. If it does need to be a Handle object, there is probably some GHC black-magic you can do, but I recommend against it if at all possible. You can ask for more details if you want. If you're using unix, there might be something you can do with the underlying unix file descriptors, but I don't know much about that. Antoine
-- Manfred
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On Mon, 13 Jun 2011 12:51:02 -0500
Antoine Latter
On Mon, Jun 13, 2011 at 12:35 PM, Manfred Lotz
wrote: Hi all, I have two handles where I get stdout resp. stderr from a command output.
Is it possible to merge those two handles so that I get a new input handle in a way that data can be read from the new handle whenever it is available from either of the two original handles?
Does what you're doing strictly need to be a handle?
One thing you could try is is using an IO Channel: http://hackage.haskell.org/packages/archive/base/latest/doc/html/Control-Con...
Hmm, not quite sure. I was asking about handles because I use: (_ ,Just hout ,Just herr ,p) <- createProcess (proc cmd parms) { std_out = CreatePipe, std_err = CreatePipe } which gives me handles to deal with. -- Manfred

On Mon, Jun 13, 2011 at 1:14 PM, Manfred Lotz
On Mon, 13 Jun 2011 12:51:02 -0500 Antoine Latter
wrote: On Mon, Jun 13, 2011 at 12:35 PM, Manfred Lotz
wrote: Hi all, I have two handles where I get stdout resp. stderr from a command output.
Is it possible to merge those two handles so that I get a new input handle in a way that data can be read from the new handle whenever it is available from either of the two original handles?
Does what you're doing strictly need to be a handle?
One thing you could try is is using an IO Channel: http://hackage.haskell.org/packages/archive/base/latest/doc/html/Control-Con...
Hmm, not quite sure. I was asking about handles because I use:
(_ ,Just hout ,Just herr ,p) <- createProcess (proc cmd parms) { std_out = CreatePipe, std_err = CreatePipe }
which gives me handles to deal with.
You could create the pipe yourself, and then call 'createProcess' with 'UseHandle' instead, passing the same handle to both std_out and std_error. On a unix-y system you can do this with the functions in System.Posix.IO. I'm not sure what you would do on windows. This might be a good question to open up to a wider audience on the haskell-cafe mailing list. Antoine

On Mon, 13 Jun 2011 15:14:26 -0500
Antoine Latter
On Mon, Jun 13, 2011 at 1:14 PM, Manfred Lotz
wrote: On Mon, 13 Jun 2011 12:51:02 -0500 Antoine Latter
wrote: On Mon, Jun 13, 2011 at 12:35 PM, Manfred Lotz
wrote: Hi all, I have two handles where I get stdout resp. stderr from a command output.
Is it possible to merge those two handles so that I get a new input handle in a way that data can be read from the new handle whenever it is available from either of the two original handles?
Does what you're doing strictly need to be a handle?
One thing you could try is is using an IO Channel: http://hackage.haskell.org/packages/archive/base/latest/doc/html/Control-Con...
Hmm, not quite sure. I was asking about handles because I use:
(_ ,Just hout ,Just herr ,p) <- createProcess (proc cmd parms) { std_out = CreatePipe, std_err = CreatePipe }
which gives me handles to deal with.
You could create the pipe yourself, and then call 'createProcess' with 'UseHandle' instead, passing the same handle to both std_out and std_error.
On a unix-y system you can do this with the functions in System.Posix.IO.
I'm not sure what you would do on windows. This might be a good
I'm on a Linux system. Don't use Windows. Thanks for pointing to this. In the meantime I found something similar in the online book "Real World Haskell". So I have something to try out. -- Manfred

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.
On Tue, Jun 14, 2011 at 11:26 AM, Manfred Lotz
On Mon, 13 Jun 2011 15:14:26 -0500 Antoine Latter
wrote: On Mon, Jun 13, 2011 at 1:14 PM, Manfred Lotz
wrote: On Mon, 13 Jun 2011 12:51:02 -0500 Antoine Latter
wrote: On Mon, Jun 13, 2011 at 12:35 PM, Manfred Lotz
wrote: Hi all, I have two handles where I get stdout resp. stderr from a command output.
Is it possible to merge those two handles so that I get a new input handle in a way that data can be read from the new handle whenever it is available from either of the two original handles?
Does what you're doing strictly need to be a handle?
One thing you could try is is using an IO Channel: http://hackage.haskell.org/packages/archive/base/latest/doc/html/Control-Con...
Hmm, not quite sure. I was asking about handles because I use:
(_ ,Just hout ,Just herr ,p) <- createProcess (proc cmd parms) { std_out = CreatePipe, std_err = CreatePipe }
which gives me handles to deal with.
You could create the pipe yourself, and then call 'createProcess' with 'UseHandle' instead, passing the same handle to both std_out and std_error.
On a unix-y system you can do this with the functions in System.Posix.IO.
I'm not sure what you would do on windows. This might be a good
I'm on a Linux system. Don't use Windows.
Thanks for pointing to this. In the meantime I found something similar in the online book "Real World Haskell". So I have something to try out.
-- Manfred
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On Tue, 14 Jun 2011 13:10:36 -0400
David McBride
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

The problem is the "forever" in the main thread. It never has a way
to know that the two threads have died, but the stm knows that the
other two channels have disappeared, so they no longer block, and this
causes a busy loop.
So check this out. I would have rather done it with a state monad to
count the number of threads I spawn and then wait for the appropriate
number of messages to arrive, but this way works too.
This is one of those cases where datatypes are awesome. Now the
thread passes back either a line to be printed, or it tells the parent
thread that it has nothing left to print. That way the main thread
knows exactly when to die.
Also, if you are going to be making command line scripts, I highly
recommend the cmdargs package on hackage, as it is pretty cool for
doing commandline arguments in a safe way.
{-# LANGUAGE ScopedTypeVariables #-}
module Main where
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)
data Message = MString String | ImDone
makeThread :: Handle -> TChan Message -> IO ThreadId
makeThread handle chan = forkIO $ (loop `catch` (\(e :: SomeException)
-> writeDone chan))
where
loop = do
msg <- hGetLine handle
writeMsg chan msg
loop
writeMsg chan msg = (atomically . writeTChan chan) $ MString msg
writeDone chan = (atomically . writeTChan chan) ImDone
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 Message)
makeThread hout chan
makeThread herr chan
printCmd chan
printCmd chan
where
printCmd chan = do
msg <- atomically (readTChan chan)
case msg of
MString msg -> do
putStrLn msg
printCmd chan
ImDone -> return ()
main :: IO ()
main = do
args <- getArgs
let cmd = head args
let parms = tail args
issueCmd cmd parms
print "Done"
On Wed, Jun 15, 2011 at 9:23 AM, Manfred Lotz
On Tue, 14 Jun 2011 13:10:36 -0400 David McBride
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
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On Wed, 15 Jun 2011 10:33:21 -0400
David McBride
The problem is the "forever" in the main thread. It never has a way to know that the two threads have died, but the stm knows that the other two channels have disappeared, so they no longer block, and this causes a busy loop.
So check this out. I would have rather done it with a state monad to count the number of threads I spawn and then wait for the appropriate number of messages to arrive, but this way works too.
This is one of those cases where datatypes are awesome. Now the thread passes back either a line to be printed, or it tells the parent thread that it has nothing left to print. That way the main thread knows exactly when to die.
Thanks a lot. I will study your solution carefully.
Also, if you are going to be making command line scripts, I highly recommend the cmdargs package on hackage, as it is pretty cool for doing commandline arguments in a safe way.
Yes, you are right of course. But here I wanted to have just a minimal example. -- Manfred

The IO Channel antoine recommended is a very elegant solution to this.
main = do
let cmd = ..., parms =...
(_ ,Just hout ,Just herr ,p) <- createProcess (proc cmd parms)
chan <- newTChanIO :: IO (TChan String)
makeThread hout chan
makeThread herr chan
forever $ atomically $ readTchan chan >>= print
makeThread handle chan = forkIO $ forever $ do
hGetLine handle >>= atomically (writeTchan chan)
I haven't run this code, but this is the general idea that I've used
many times. The threads run taking input from their sources and
shoving it down the channel. The main thread continually reads
messages from the channel and blocks while it waits for new messages
to arrive.
On Mon, Jun 13, 2011 at 2:14 PM, Manfred Lotz
On Mon, 13 Jun 2011 12:51:02 -0500 Antoine Latter
wrote: On Mon, Jun 13, 2011 at 12:35 PM, Manfred Lotz
wrote: Hi all, I have two handles where I get stdout resp. stderr from a command output.
Is it possible to merge those two handles so that I get a new input handle in a way that data can be read from the new handle whenever it is available from either of the two original handles?
Does what you're doing strictly need to be a handle?
One thing you could try is is using an IO Channel: http://hackage.haskell.org/packages/archive/base/latest/doc/html/Control-Con...
Hmm, not quite sure. I was asking about handles because I use:
(_ ,Just hout ,Just herr ,p) <- createProcess (proc cmd parms) { std_out = CreatePipe, std_err = CreatePipe }
which gives me handles to deal with.
-- Manfred
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On Mon, 13 Jun 2011 16:59:11 -0400
David McBride
The IO Channel antoine recommended is a very elegant solution to this.
main = do let cmd = ..., parms =... (_ ,Just hout ,Just herr ,p) <- createProcess (proc cmd parms) chan <- newTChanIO :: IO (TChan String) makeThread hout chan makeThread herr chan forever $ atomically $ readTchan chan >>= print
makeThread handle chan = forkIO $ forever $ do hGetLine handle >>= atomically (writeTchan chan)
Thanks for the code. I added import GHC.Conc.Sync import System.IO import System.Environment import System.Process import Control.Monad import Control.Concurrent.STM.TChan but when compiling I get: cmdtest2.hs:17:45: Couldn't match expected type `STM a0' with actual type `IO ()' Expected type: String -> STM a0 Actual type: String -> IO () In the second argument of `(>>=)', namely `print' In the second argument of `($)', namely `readTChan chan >>= print' cmdtest2.hs:20:23: Couldn't match expected type `String -> IO a0' with actual type `IO a1' In the return type of a call of `atomically' In the second argument of `(>>=)', namely `atomically (writeTChan chan)' In the expression: hGetLine handle >>= atomically (writeTChan chan) I'm still too much in the dark regarding the monad stuff thus having no idea how to fix it. -- Manfred
participants (3)
-
Antoine Latter
-
David McBride
-
Manfred Lotz