{-|
    Module      :  Data.Number.ER.Misc.STM
    Description :  some STM extras 
    Copyright   :  (c) Michal Konecny
    License     :  BSD3

    Maintainer  :  mik@konecny.aow.cz
    Stability   :  experimental
    Portability :  portable
    
    Miscelaneous utilities related to concurrency.
-}
module Data.Number.ER.Misc.STM where

import Control.Concurrent as Concurrent
import Control.Concurrent.STM as STM

modifyTVar tv update =
    do
    value <- readTVar tv
    let newValue = update value
    writeTVar tv newValue
    return newValue

modifyTVarGetOldVal tv update =
    do
    value <- readTVar tv
    writeTVar tv $ update value
    return value

modifyTVarHasChanged tv update =
    do
    value <- readTVar tv
    let newValue = update value
    if value == newValue
        then return False
        else 
            do
            writeTVar tv $ update value
            return True