[Haskell-cafe] Implementing computations with timeout

Tomasz Zielonka tomasz.zielonka at gmail.com
Fri Jan 7 10:24:45 EST 2005


On Fri, Jan 07, 2005 at 02:57:19PM +0100, Tomasz Zielonka wrote:
> My guess is it would be something like this, however you may want to do it
> differently to get better compositionality (withTimeout returns an IO action,
> not a STM action):

Maybe this will suffice, but I don't know if the delay thread will be
garbage collected.

  import Control.Concurrent
  import Control.Concurrent.STM
  import Monad (when)

  makeDelay :: Int -> IO (STM ())
  makeDelay time = do
      v <- atomically (newTVar False)
      forkIO $ do
          threadDelay time
          atomically (writeTVar v True)
      return $ readTVar v >>= \b -> when (not b) retry

  withTimeout :: Int -> STM a -> IO (Maybe a)
  withTimeout time fun = do
      delay <- makeDelay time
      atomically (fmap Just fun `orElse` (delay >> return Nothing))

Best regards,
Tomasz


More information about the Haskell-Cafe mailing list