stm-stats-0.2.0.0: retry statistics for STM transactions

Portabilitynon-portable (requires STM)
MaintainerJoachim Breitner <mail@joachim-breitner.de>

Control.Concurrent.STM.Stats

Contents

Description

This module provides variants to the function atomically from Control.Concurrent.STM which keep track of how often the transaction is initiated and how often it was retried.

Synopsis

Example usage

The following example code shows how to use the module:

import Control.Concurrent
import Control.Concurrent.STM
import Control.Monad

import Control.Concurrent.STM.Stats

main = do
     var <- trackSTM $ newTVar 0
     forkIO $ forM_ [1..23] $ i -> do
         threadDelay (100*1000)
         trackNamedSTM "writer" $ writeTVar var i
     putStrLn "Starting reader..."
     trackNamedSTM "reader" $ do
         i <- readTVar var
         when (i < 23) retry
     putStrLn "Reader finished."
     dumpSTMStats

Running this program will result in this output:

Starting reader...
STM transaction reader finished after 23 retries
Reader finished.
STM transaction statistics (2011-10-09 12:28:37.188951 UTC):
Transaction     Commits    Retries      Ratio
_anonymous_           1          0       0.00
reader                1         23      23.00
writer               23          0       0.00

The function trackSTM is a direct replacement for atomically, while trackNamedSTM and trackSTMConf provide more control and $trackThisSTM uses Template Haskell to automatically generate a good name.

Generating statistics

trackSTM :: STM a -> IO aSource

A drop-in replacement for atomically. The statistics will list this, and all other unnamed transactions, as "_anonymous_" and BlockedIndefinitelyOnSTM exceptions will not be replaced. See below for variants that give more control over the statistics and generated warnings.

trackNamedSTM :: String -> STM a -> IO aSource

Run atomically and collect the retry statistics under the given name and using the default configuration, defaultTrackSTMConf.

trackThisSTM :: Q ExpSource

This, when used as $trackThisSTM in a module with -XTemplateHaskell enabled, will call trackNamedSTM with a name automatically derived from the source file name and position, e.g. "Test.hs:6:21".

trackSTMConf :: TrackSTMConf -> String -> STM a -> IO aSource

Run atomically and collect the retry statistics under the given name, while issuing warnings when the configured thresholds are exceeded.

Configuring TrackSTM

data TrackSTMConf Source

For the most general transaction tracking function, trackSTMConf, all settings can be configured using a TrackSTMConf value.

Constructors

TrackSTMConf 

Fields

tryThreshold :: Maybe Int

If the number of retries of one transaction run reaches this count, a warning is issued at runtime. If set to Nothing, disables the warnings completely.

globalTheshold :: Maybe Int

If the total number of retries of one named transaction reaches this count, a warning is issued. If set to Nothing, disables the warnings completely.

extendException :: Bool

If this is set, a BlockedIndefinitelyOnSTM exception is replaced by a BlockedIndefinitelyOnNamedSTM exception, carrying the name of the exception.

warnFunction :: String -> IO ()

Function to call when a warning is to be emitted.

warnInSTMFunction :: String -> IO ()

Function to call when a warning is to be emitted during an STM transaction. This is possibly dangerous, see the documentation to unsafeIOToSTM, but can be useful to detect transactions that keep retrying forever.

defaultTrackSTMConf :: TrackSTMConfSource

The default settings are:

 defaultTrackSTMConf = TrackSTMConf
    { tryThreshold =      Just 10
    , globalTheshold =    Just 3000
    , exception =         True
    , warnFunction =      hPutStrLn stderr
    , warnInSTMFunction = \_ -> return ()
    }

More helpful exceptions

data BlockedIndefinitelyOnNamedSTM Source

If extendException is set (which is the case with trackNamedSTM), an occurrence of BlockedIndefinitelyOnSTM is replaced by BlockedIndefinitelyOnNamedSTM, carrying the name of the transaction and thus giving more helpful error messages.

Reading the statistics

getSTMStats :: IO (Map String (Int, Int))Source

Fetches the current transaction statistics data.

The map maps transaction names to counts of transaction commits and transaction retries.

dumpSTMStats :: IO ()Source

Dumps the current transaction statistics data to stderr.