stm-delay-0.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

Suppose you are managing a network connection, and want to time it out if no messages are received in over five minutes. You can do something like this:

import Control.Concurrent.Async (race_) -- from the async package
import Control.Concurrent.STM
import Control.Concurrent.STM.Delay
import Control.Exception
import Control.Monad

manageConnection :: Connection -> IO Message -> (Message -> IO a) -> IO ()
manageConnection conn toSend onRecv =
    bracket (newDelay five_minutes) cancelDelay $ \delay ->
    foldr1 race_
        [ do atomically $ waitDelay delay
             fail "Connection timed out"
        , forever $ toSend >>= send conn
        , forever $ do
            msg <- recv conn
            updateDelay delay five_minutes
            onRecv msg
        ]
  where
    five_minutes = 5 * 60 * 1000000

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.