----------------------------------------------------------------------------- -- | -- Module : Control.Monad.AdvSTM.Class -- Copyright : (c) HaskellWiki 2006-2007, Peter Robinson 2008 -- License : BSD3 -- -- Maintainer : Peter Robinson -- Stability : experimental -- Portability : non-portable (requires STM) -- -- Provides the type class MonadAdvSTM -- Parts of this implementation were taken from the HaskellWiki Page of -- MonadAdvSTM (see package description). ----------------------------------------------------------------------------- module Control.Monad.AdvSTM.Class( MonadAdvSTM(..)) where import Control.Exception(Exception,Deadlock) import qualified Control.Concurrent.STM as S import Control.Monad(Monad) import Control.Monad.AdvSTM.Def(AdvSTM) -- | A type class for extended-STM monads. For a concrete instantiation see -- 'AdvSTM' class Monad m => MonadAdvSTM m where -- | Takes an IO action that will be executed iff the transaction commits. -- -- * When a TVar was modified in a transaction and this transaction commits, -- this update remains invisible to other threads until the corresponding -- onCommit action was run. -- -- * If the onCommit action throws an exception, the original value of -- the TVars will be restored. -- -- * Accessing a modified TVar within the onCommit action will cause a -- 'Deadlock' exception to be thrown. -- -- As a general rule, 'onCommit' should -- only be used for \"real\" (i.e. without atomic blocks) IO actions and is certainly -- not the right place to fiddle with TVars. For example, if you wanted to -- write a TVar value to a file on commit, you could write: -- -- > tvar <- newTVarIO "bla" -- > atomically $ do -- > x <- readTVar tvar -- > onCommit (writeFile "myfile" x) -- -- onCommit :: IO () -> m () -- | Adds an IO action to the retry job-queue. If the transaction retries, -- a new helper thread is forked that runs the retry actions, and, after the helper -- thread is done, the transaction retries. -- /Warning:/ Uses unsafeIOToSTM to fork a helper thread that runs the retry -- actions! unsafeOnRetry :: IO () -> m () -- | See 'S.orElse' orElse :: m a -> m a -> m a -- | See 'S.retry'. Skips any IO actions added by unsafeOnRetry. retry :: m a -- | See 'S.check' check :: Bool -> m () -- | See 'S.alwaysSucceeds' alwaysSucceeds :: m a -> m () -- | See 'S.always' always :: m Bool -> m () -- | Runs a transaction atomically in the 'IO' monad. runAtomic :: m a -> IO a -- | See 'S.catchSTM' catchSTM :: Exception e => m a -> (e -> m a) -> m a -- | Lifts STM actions to 'MonadAdvSTM'. liftAdv :: S.STM a -> m a