Some problems writing a threaded program

I am running my program in WinXP with ghc 2.6.8 If you install netstat and change the parameters it should still work in linux. Why does thread # 3 dominate over the over threads int the output? Why does thread # 4 never seem to run? I can't use the sleep function in System.Process.Win32 since it puts all the threads asleep at the same time. Is there a way to put only one thread asleep? That would allow more of a chance for thread #4 to run. The simplified program: --------------------------------------------------------------- module Main where import Data.IORef import Data.List import System.IO import System.Process import Control.Concurrent import Control.Concurrent.Chan data Connection = Null | Last | Active deriving (Eq) instance Show Connection where show Null = "Null" show Last = "Last" show Active = "Active" instance Read Connection where readsPrec _ s = case take 5 s of " UDP" -> [(Active, "")] " TCP" -> [(Active, "")] "Last" -> [(Last,"")] _ -> [(Null,"")] -- ptrints one 0 and 1 main = do stop <- newIORef False cbuffer <- newChan :: IO (Chan Connection) putStr "0" (_,output,_,ph) <- runInteractiveCommand "netstat -noa 5" sequence $ map forkIO $ [(processConnections ph output cbuffer), (stopNetstat ph stop False), (printChan cbuffer),(checkStop stop "xxxx")] putStr "1" _ <- waitForProcess ph --mapM killThread ts putStrLn "\nDone" -- thread # 2 processConnections :: ProcessHandle -> Handle -> (Chan Connection) -> IO () processConnections ph hout chan = do h <- hReady hout e <- getProcessExitCode ph putStr "2" if (not h && e /= Nothing) then do writeChan chan Last >> return () else do if h then do readConnection hout >>= writeChan chan else do processConnections ph hout chan readConnection :: Handle -> IO Connection readConnection hout = do l <- hGetLine hout let c = (read l :: Connection) if (c == Null) then do (readConnection hout) else do (return c) -- thread number 3 stopNetstat :: ProcessHandle -> (IORef Bool) -> Bool -> IO () stopNetstat netstat _ True = terminateProcess netstat stopNetstat netstat gref False = putStr "3" >> yield >> readIORef gref >>= stopNetstat netstat gref --thread 4 printChan :: (Chan Connection) -> IO () printChan chan = do putStr "4" c <- readChan chan printConnection c printChan chan checkStop :: (IORef Bool) -> String -> IO () checkStop ref s = do if (take 4 s == "stop") then do (writeIORef ref True) else do (getChar >>= (\x -> checkStop ref ((tail s) ++ [x]))) printConnection :: Connection -> IO () printConnection c = case c of Null -> putStr "N" Last -> putStr "L" _ -> putStr "A"

jpvogel1:
I am running my program in WinXP with ghc 2.6.8
If you install netstat and change the parameters it should still work in linux.
Why does thread # 3 dominate over the over threads int the output? Why does thread # 4 never seem to run?
I can't use the sleep function in System.Process.Win32 since it puts all the threads asleep at the same time. Is there a way to put only one thread asleep?
That would allow more of a chance for thread #4 to run.
There is 'threadDelay' and 'yield' if you need to either sleep a thread, or explicitly trigger a scheduler event. http://haskell.org/ghc/docs/latest/html/libraries/base/Control-Concurrent.ht...

John Vogel wrote:
I am running my program in WinXP with ghc 2.6.8
If you install netstat and change the parameters it should still work in linux.
Why does thread # 3 dominate over the over threads int the output? Why does thread # 4 never seem to run?
I can't use the sleep function in System.Process.Win32 since it puts all the threads asleep at the same time. Is there a way to put only one thread asleep?
That would allow more of a chance for thread #4 to run.
I haven't looked in detail at what happens in your program, but there is a matter of style here: you appear to be using busy-waiting and polling a lot. GHC's runtime shouldn't be considered "fair" in any sense other than the most basic: a thread will get to run eventually, but if it immediately blocks then it loses its timeslice. There's no guarantee that a thread will get a fair share of the CPU. So busy-waiting and polling will often suffer from a lack of fairness in the scheduler. Let me be a little more concrete: you're doing a lot of output to stdout. Now, stdout has a lock on it - only one thread can be holding stdout at any one time. Often, a thread will be preempted while holding the stdout lock, and since the other threads are all waiting to output to stdout too, none of them can make progress, so the original thread gets another timeslice (unfair!). This is why, if you try to write one of those AAAABBBB... concurrency tests using GHC, you'll probably get AAAAAAAAAA... GHC's scheduler is intentionally simple, because it is designed to cope with workloads that consist of mostly *blocked* threads, and a very few running threads. However, you might get more fairness using a couple of cores and running with +RTS -N2. Perhaps one day we'll have to consider questions of fairness and priority, hopefully in the context of a user-programmable scheduler. But for now, this is the way it is. Cheers, Simon

Thankyou both Don Stewart and Simon Marlow for your responses.
By adding yield and threadDelay in certain spots I have at least prevented some of the threads from being starved of CPU time. The only issue now is that terminateProcess doesn't always terminate netstat.exe in the cmd.exe so I don't get an exit condition.

John Vogel wrote:
Thankyou both Don Stewart and Simon Marlow for your responses.
By adding yield and threadDelay in certain spots I have at least prevented some of the threads from being starved of CPU time.
The only issue now is that terminateProcess doesn't always terminate netstat.exe in the cmd.exe so I don't get an exit condition.
Windows doesn't have the same concept of process groups that Unix has, so killing a shell doesn't necessarily kill its children. Have a look at the hoops Ian had to jump through to get this working for our timeout program in the GHC testsuite: http://darcs.haskell.org/testsuite/timeout/ Cheers, Simon

2008/2/11 John Vogel
The only issue now is that terminateProcess doesn't always terminate netstat.exe in the cmd.exe so I don't get an exit condition.
A simple way is to use runInteractiveProcess instead of runInteractiveCommand. The former doesn't start a new cmd.exe but starts netstat.exe directly. There isn't point of using runInteractiveCommand unless you want to execute some shell commands or batch files. Regards, Krasimir
participants (4)
-
Don Stewart
-
John Vogel
-
Krasimir Angelov
-
Simon Marlow