Re: Some problems writing a threaded program

2008-02-10 Thread Don Stewart
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.html#4
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Some problems writing a threaded program

2008-02-10 Thread John Vogel
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 )]
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
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users