stm-delay-0.1.1: Updatable one-shot timer polled with STM

PortabilityRequires GHC 7+
Maintainerjoeyadams3.14159@gmail.com
Safe HaskellSafe-Inferred

Control.Concurrent.STM.Delay

Contents

Description

One-shot timer whose duration can be updated. Think of it as an enhanced version of registerDelay.

This uses GHC.Event when available (GHC 7.2+, -threaded, non-Windows OS). Otherwise, it falls back to forked threads and threadDelay.

Synopsis

Managing delays

data Delay Source

A Delay is an updatable timer that rings only once.

Instances

newDelay :: Int -> IO DelaySource

Create a new Delay that will ring in the given number of microseconds.

updateDelay :: Delay -> Int -> IO ()Source

Set an existing Delay to ring in the given number of microseconds (from the time updateDelay is called), rather than when it was going to ring. If the Delay has already rung, do nothing.

cancelDelay :: Delay -> IO ()Source

Set a Delay so it will never ring, even if updateDelay is used later. If the Delay has already rung, do nothing.

Waiting for expiration

waitDelay :: Delay -> STM ()Source

Block until the Delay rings. If the Delay has already rung, return immediately.

tryWaitDelay :: Delay -> STM BoolSource

Non-blocking version of waitDelay. Return True if the Delay has rung.

tryWaitDelayIO :: Delay -> IO BoolSource

Faster version of atomically . tryWaitDelay. See readTVarIO.

Since 0.1.1

Example

Suppose we are managing a network connection, and want to time it out if no messages are received in over five minutes. We'll create a Delay, and an action to "bump" it:

  let timeoutInterval = 5 * 60 * 1000000 :: Int
  delay <- newDelay timeoutInterval
  let bump = updateDelay delay timeoutInterval

This way, the Delay will ring if it is not bumped for longer than five minutes.

Now we fork the receiver thread:

  dead <- newEmptyTMVarIO
  _ <- forkIO $
    (forever $ do
         msg <- recvMessage
         bump
         handleMessage msg
     ) `finally` atomically (putTMVar dead ())

Finally, we wait for the delay to ring, or for the receiver thread to fail due to an exception:

  atomically $ waitDelay delay `orElse` readTMVar dead

Warning:

  • If handleMessage blocks, the Delay may ring due to handleMessage taking too long, rather than just recvMessage taking too long.
  • The loop will continue to run until you do something to stop it.

It might be simpler to use System.Timeout instead:

  m <- timeout timeoutInterval recvMessage
  case m of
      Nothing  -> fail "timed out"
      Just msg -> handleMessage msg

However, using a Delay has the following advantages:

  • If recvMessage makes a blocking FFI call (e.g. network I/O on Windows), timeout won't work, since it uses an asynchronous exception, and FFI calls can't be interrupted with async exceptions. The Delay approach lets you handle the timeout in another thread, while the FFI call is still blocked.
  • updateDelay is more efficient than timeout when GHC.Event is available.