| Copyright | (c) 2016 Michael Walker | 
|---|---|
| License | MIT | 
| Maintainer | Michael Walker <mike@barrucadu.co.uk> | 
| Stability | stable | 
| Portability | portable | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Control.Concurrent.Classy.STM.TVar
Contents
Description
Transactional variables, for use with MonadSTM.
Deviations: There is no Eq instance for MonadSTM the TVar
 type. Furthermore, the newTVarIO and mkWeakTVar functions are
 not provided.
Synopsis
- type family TVar stm :: * -> *
- newTVar :: MonadSTM stm => a -> stm (TVar stm a)
- newTVarN :: MonadSTM stm => String -> a -> stm (TVar stm a)
- readTVar :: MonadSTM stm => TVar stm a -> stm a
- readTVarConc :: MonadConc m => TVar (STM m) a -> m a
- writeTVar :: MonadSTM stm => TVar stm a -> a -> stm ()
- modifyTVar :: MonadSTM stm => TVar stm a -> (a -> a) -> stm ()
- modifyTVar' :: MonadSTM stm => TVar stm a -> (a -> a) -> stm ()
- stateTVar :: MonadSTM stm => TVar stm s -> (s -> (a, s)) -> stm a
- swapTVar :: MonadSTM stm => TVar stm a -> a -> stm a
- registerDelay :: MonadConc m => Int -> m (TVar (STM m) Bool)
TVars
type family TVar stm :: * -> * Source #
The mutable reference type. These behave like TVars, in that
 they always contain a value and updates are non-blocking and
 synchronised.
Since: 1.0.0.0
Instances
| type TVar STM Source # | |
| Defined in Control.Monad.STM.Class | |
| type TVar (IsSTM m) Source # | |
| Defined in Control.Monad.STM.Class | |
| type TVar (WriterT w stm) Source # | |
| Defined in Control.Monad.STM.Class | |
| type TVar (StateT s stm) Source # | |
| Defined in Control.Monad.STM.Class | |
| type TVar (IdentityT stm) Source # | |
| Defined in Control.Monad.STM.Class | |
| type TVar (StateT s stm) Source # | |
| Defined in Control.Monad.STM.Class | |
| type TVar (WriterT w stm) Source # | |
| Defined in Control.Monad.STM.Class | |
| type TVar (ReaderT r stm) Source # | |
| Defined in Control.Monad.STM.Class | |
| type TVar (RWST r w s stm) Source # | |
| Defined in Control.Monad.STM.Class | |
| type TVar (RWST r w s stm) Source # | |
| Defined in Control.Monad.STM.Class | |
newTVar :: MonadSTM stm => a -> stm (TVar stm a) Source #
Create a new TVar containing the given value.
newTVar = newTVarN ""
Since: 1.0.0.0
newTVarN :: MonadSTM stm => String -> a -> stm (TVar stm a) Source #
Create a new TVar containing the given value, but it is
 given a name which may be used to present more useful debugging
 information.
If an empty name is given, a counter starting from 0 is used. If
 names conflict, successive TVars with the same name are given
 a numeric suffix, counting up from 1.
newTVarN _ = newTVar
Since: 1.0.0.0
readTVar :: MonadSTM stm => TVar stm a -> stm a Source #
Return the current value stored in a TVar.
Since: 1.0.0.0
readTVarConc :: MonadConc m => TVar (STM m) a -> m a Source #
Read the current value stored in a TVar. This may be
 implemented differently for speed.
readTVarConc = atomically . readTVar
Since: 1.0.0.0
writeTVar :: MonadSTM stm => TVar stm a -> a -> stm () Source #
Write the supplied value into the TVar.
Since: 1.0.0.0
modifyTVar :: MonadSTM stm => TVar stm a -> (a -> a) -> stm () Source #
Mutate the contents of a TVar. This is non-strict.
Since: 1.0.0.0
modifyTVar' :: MonadSTM stm => TVar stm a -> (a -> a) -> stm () Source #
Mutate the contents of a TVar strictly.
Since: 1.0.0.0
stateTVar :: MonadSTM stm => TVar stm s -> (s -> (a, s)) -> stm a Source #
Like modifyTVar' but the function is a simple state transition that can
 return a side value which is passed on as the result of the STM.
Since: 1.6.1.0
swapTVar :: MonadSTM stm => TVar stm a -> a -> stm a Source #
Swap the contents of a TVar, returning the old value.
Since: 1.0.0.0
registerDelay :: MonadConc m => Int -> m (TVar (STM m) Bool) Source #
Set the value of returned TVar to True after a given number
 of microseconds. The caveats associated with threadDelay also
 apply.
Since: 1.0.0.0