[Haskell-cafe] Concurrency question
Donald Bruce Stewart
dons at cse.unsw.edu.au
Sun Sep 4 21:37:55 EDT 2005
akamaus:
> Donald Bruce Stewart wrote:
>
> >Maybe your loop does no allocations, so the scheduler can't get in and do a
> >context switch. You could put the computation in an external program, and
> >run
> >it over a fork, using unix signals in the external program to kill the
> >computation after a period of time.
>
> I thought about doing that, but function is closely connected with the
> rest of the program. Running it in another process would require some
> parsing of its arguments and I want circumvent these difficulties.
Ah, I've found another example. This function attempts to run an
expensive computation. If it doesn't return within a given time, a cheap
function is used instead. This was mostly written by Stefan Wehr:
watchdogIO :: Int -- milliseconds
-> IO a -- expensive computation
-> IO a -- cheap computation
-> IO a
watchdogIO millis expensive cheap = do
mvar <- newEmptyMVar
tid1 <- forkIO $ do x <- expensive
x `seq` putMVar mvar (Just x)
tid2 <- forkIO $ do threadDelay (millis * 1000)
putMVar mvar Nothing
res <- takeMVar mvar
case res of
Just x -> do
info ("EXPENSIVE was used")
killThread tid2 `catch` (\e -> warn (show e))
return x
Nothing -> do
info ("WATCHDOG after " ++ show millis ++ " milliseconds")
killThread tid1 `catch` (\e -> warn (show e))
cheap
-- Don
More information about the Haskell-Cafe
mailing list