[Haskell-cafe] Haskell thread preemption

Dmitry Vyal akamaus at gmail.com
Wed Aug 31 09:17:55 EDT 2005


Hello, all.

I'm experimenting with concurrent haskell using GHC 6.4.
I wrote these fuctions as described in "Tackling the Awkward Squad":

par_io :: IO a -> IO a -> IO a
par_io t1 t2 = do c <- newEmptyMVar :: IO (MVar a)
                   id1 <- forkIO $ wrapper c t1
                   id2 <- forkIO $ wrapper c t2
                   res <- takeMVar c
                   killThread id1
                   killThread id2
                   return res
     where wrapper :: MVar a -> IO a -> IO ()
           wrapper mvar io = do res <- io
                                putMVar mvar res


timeout :: Int -> IO a -> IO (Maybe a)
timeout n t = do res <- par_io thr timer
                  return res
     where thr = do res <- t
                    return $ Just res
           timer = do threadDelay n
                      return Nothing

Now, then I try something like
	timeout 1000000 (print $ cycle "test")

it behaves correctly: repeatingly prints "test" for one second and then 
returns Nothing.

But then I try this:
timeout 1000000 (print $ 2^2^2^2^2^2)

it hangs for about eight seconds.

Currently I'm playing with theorem-proving using resolution. So I need 
some technique to break a computation, if takes too long. It seems that 
using "timeout" there does nothing. I waited for several minutes for 
invalid theorem and timeout didn't expire.

"Control.Concurrent" page of "Haskell Hierarchical Libraries" says, that 
a thread may be pre-empted whenever it allocates some memory, and that 
tight loops which do no allocation tend to lock out other threads.

But resolution function, i wrote, hogs a *lot* of memory and (print $ 
2^2^2^2^2^2) does either. So i'm curious about this behavior of timeout.

So what is the correct way of running such computations in parallel?
Maybe I'm missing something?



More information about the Haskell-Cafe mailing list