[Haskell] timing/timeout (how to express that in Haskell)

Donald Bruce Stewart dons at cse.unsw.edu.au
Fri May 12 05:36:18 EDT 2006


rahn:
> Donald Bruce Stewart wrote:
> 
> >    watchdogIO :: Int  -- milliseconds
> >             -> IO a   -- expensive computation
> >             -> IO a   -- cheap computation
> >             -> IO a
> 
> I'm not satisfied by the given function completely. Suppose the wrappers 
> for pure computations
> 
> watchdog1 :: Int -> a -> IO (Maybe a)
> watchdog1 millis x =
>     watchdogIO millis (return (Just x))
>                       (return Nothing)
> 
> watchdog2 :: Int -> a -> IO (Maybe a)
> watchdog2 millis x =
>     watchdogIO millis (x `seq` return (Just x))
>                       (return Nothing)
> 
> and the (expensive) function
> 
> grundy :: Integer -> Integer
> grundy n = mex [ grundy k | k <- [0..pred n] ]
>     where mex xs = head [ k | k <- [0..] , not (elem k xs) ]
> 
> Now
> 
> *NG> Util.IO.Within.watchdog1 1000 (grundy 15) >>= print
> EXPENSIVE was used
> Just 15
> (0.26 secs, 12677644 bytes)
> *NG> Util.IO.Within.watchdog1 1000 (grundy 20) >>= print
> EXPENSIVE was used
> Just 20
> (8.35 secs, 395376708 bytes)
> 
> So watchdog1 is'nt the right choice. Let's use watchdog2:
> 
> *NG> Util.IO.Within.watchdog2 1000 (grundy 15) >>= print
> EXPENSIVE was used
> Just 15
> (0.27 secs, 13075340 bytes)
> *NG> Util.IO.Within.watchdog2 1000 (grundy 20) >>= print
> WATCHDOG after 1000 milliseconds
> Nothing
> (1.08 secs, 49634204 bytes)
> 
> Looks better, but:
> 
> *NG> Util.IO.Within.watchdog2 1000 (map grundy [0..20]) >>= print
> EXPENSIVE was used
> Just [0,1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20]
> (16.81 secs, 790627600 bytes)
> 
> So what we really need is a deepSeq once more.

Yes, I think this came up once. We should be using deepSeq there.

Note that this could was produced in the heat of last year's ICFP
contest, so probably can be excused if it isn't fully tested :)

-- Don


More information about the Haskell mailing list