[Haskell] timing/timeout (how to express that in Haskell)
Donald Bruce Stewart
dons at cse.unsw.edu.au
Fri May 12 04:01:36 EDT 2006
waldmann:
> What is the idiomatic way to say in (ghc) Haskell:
> "run this computation for at most x seconds"
> (e. g. it returns Boolean; imagine a primality test)
> so I want something :: Int -> a -> Maybe a
> with the guarantee that the result is
> Just x with x in whnf, or Nothing.
> I guess one answer is "that's not Haskell because
> that's not a function". Sure, but I think I need it
> anyways, so I would accept some IO .. in the types.
This comes up occasionally, at least one solution is:
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
Note that this does more than you want, but you get the idea.
forkIO + killThread && threadDelay
If you code up a nice example, perhaps you coudl put it on the wiki,
under Idioms?
-- Don
More information about the Haskell
mailing list