Hello Joel,

Tuesday, November 22, 2005, 1:41:38 AM, you wrote:

JR> logger h die =
JR>      do empty <- isEmptyChan parent
JR>         unless empty $ do x <- readChan parent
JR>                           putStrLn x
JR>                           hPutStrLn h x
JR>         alive <- isEmptyMVar die
JR>         when (alive || not empty) $ logger h die

can you just send Die message through the same Chan? it will be best
solution. you can even write:

logger h die =
     pid <- forkIO (readMVar die >> putChan parent DIE)
     go
     killThread pid
     where go = do x <- readChan parent
                   case x of
                     DIE -> return ()
                     _ -> do putStrLn x
                             hPutStrLn h x
                             go



or try something like this:

while isEmptyMVar
  while not isEmptyChan
    x <- readChan
    ...

JR> I see clearly how using Maybe with getChanContents will work out
JR> perfectly. I don't understand why the above code is inefficient to  
JR> the point of printing just a few messages (out of hundreds) out on  
JR> Windows. I would like to understand it to avoid such mistakes in the  
JR> future.

is writing to channel and filling MVar done in different threads? if
so, second thread may just get much more attention. and may be your
code itself drive to this, for example because you are querying channel state
with the same frequency as state of MVar


ps: btw, for such sort of tasks like 'go' above i created control
structure repeat_whileM. with its help first code will become just:

logger h die =
  withThread (readMVar die >> putChan parent DIE) $ do
    repeat_whileM (readChan parent) (/=DIE) (\x -> putStrLn x >> hPutStrLn h x)

withThread code  =  bracket (forkIO code) killThread . const
  
repeat_whileM inp cond out = do
  x <- inp
  if (cond x)
    then do out x
            repeat_whileM inp cond out
    else return x

-- 
Best regards,
 Bulat                            mailto:[EMAIL PROTECTED]



_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to