stm-2.5.3.0: Software Transactional Memory
Copyright(c) The University of Glasgow 2004
LicenseBSD-style (see the file libraries/base/LICENSE)
Maintainerlibraries@haskell.org
Stabilityexperimental
Portabilitynon-portable (requires STM)
Safe HaskellTrustworthy
LanguageHaskell2010

Control.Monad.STM

Description

Software Transactional Memory: a modular composable concurrency abstraction. See

This module only defines the STM monad; you probably want to import Control.Concurrent.STM (which exports Control.Monad.STM).

Note that invariant checking (namely the always and alwaysSucceeds functions) has been removed. See ticket #14324 and the removal proposal. Existing users are encouraged to encapsulate their STM operations in safe abstractions which can perform the invariant checking without help from the runtime system.

Synopsis

Documentation

data STM a #

Instances

Instances details
Alternative STM 
Instance details

Defined in GHC.Internal.Conc.Sync

Methods

empty :: STM a #

(<|>) :: STM a -> STM a -> STM a #

some :: STM a -> STM [a] #

many :: STM a -> STM [a] #

Applicative STM 
Instance details

Defined in GHC.Internal.Conc.Sync

Methods

pure :: a -> STM a #

(<*>) :: STM (a -> b) -> STM a -> STM b #

liftA2 :: (a -> b -> c) -> STM a -> STM b -> STM c #

(*>) :: STM a -> STM b -> STM b #

(<*) :: STM a -> STM b -> STM a #

Functor STM 
Instance details

Defined in GHC.Internal.Conc.Sync

Methods

fmap :: (a -> b) -> STM a -> STM b #

(<$) :: a -> STM b -> STM a #

Monad STM 
Instance details

Defined in GHC.Internal.Conc.Sync

Methods

(>>=) :: STM a -> (a -> STM b) -> STM b #

(>>) :: STM a -> STM b -> STM b #

return :: a -> STM a #

MonadPlus STM 
Instance details

Defined in GHC.Internal.Conc.Sync

Methods

mzero :: STM a #

mplus :: STM a -> STM a -> STM a #

MonadFix STM Source #

Since: stm-2.3

Instance details

Defined in Control.Monad.STM

Methods

mfix :: (a -> STM a) -> STM a #

MArray TArray e STM Source # 
Instance details

Defined in Control.Concurrent.STM.TArray

Methods

getBounds :: Ix i => TArray i e -> STM (i, i) Source #

getNumElements :: Ix i => TArray i e -> STM Int Source #

newArray :: Ix i => (i, i) -> e -> STM (TArray i e) Source #

newArray_ :: Ix i => (i, i) -> STM (TArray i e) Source #

unsafeNewArray_ :: Ix i => (i, i) -> STM (TArray i e) Source #

unsafeRead :: Ix i => TArray i e -> Int -> STM e Source #

unsafeWrite :: Ix i => TArray i e -> Int -> e -> STM () Source #

Monoid a => Monoid (STM a) 
Instance details

Defined in GHC.Internal.Conc.Sync

Methods

mempty :: STM a #

mappend :: STM a -> STM a -> STM a #

mconcat :: [STM a] -> STM a #

Semigroup a => Semigroup (STM a) 
Instance details

Defined in GHC.Internal.Conc.Sync

Methods

(<>) :: STM a -> STM a -> STM a #

sconcat :: NonEmpty (STM a) -> STM a #

stimes :: Integral b => b -> STM a -> STM a #

atomically :: STM a -> IO a #

retry :: STM a #

orElse :: STM a -> STM a -> STM a #

check :: Bool -> STM () Source #

Check that the boolean condition is true and, if not, retry.

In other words, check b = unless b retry.

Since: stm-2.1.1

throwSTM :: Exception e => e -> STM a #

catchSTM :: Exception e => STM a -> (e -> STM a) -> STM a #

Orphan instances

MonadFix STM Source #

Since: stm-2.3

Instance details

Methods

mfix :: (a -> STM a) -> STM a #