| Safe Haskell | None |
|---|
Control.Monad.Interface.MutVar
Contents
Description
This module exports:
- The
MonadMutVartype class and its operationsnewRef,readRef,writeRefandatomicModifyRef. - Instances of
MonadMutVarforIO,STM, strictSTand lazyST. - A universal pass-through instance of
MonadMutVarfor any existingMonadMutVarwrapped by aMonadLayer. - The utility operations
atomicModifyRef',atomicWriteRef,modifyRefandmodifyRef'.
- class Monad m => MonadMutVar ref m | m -> ref where
- newRef :: a -> m (ref a)
- readRef :: ref a -> m a
- writeRef :: ref a -> a -> m ()
- atomicModifyRef :: ref a -> (a -> (a, b)) -> m b
- atomicModifyRef' :: MonadMutVar ref m => ref a -> (a -> (a, b)) -> m b
- atomicWriteRef :: MonadMutVar ref m => ref a -> a -> m ()
- modifyRef :: MonadMutVar ref m => ref a -> (a -> a) -> m ()
- modifyRef' :: MonadMutVar ref m => ref a -> (a -> a) -> m ()
The MonadMutVar class
class Monad m => MonadMutVar ref m | m -> ref whereSource
The type class MonadMutVar represents the class of monads which support
mutable variables. The ref parameter is the type of the mutable variable;
e.g., for IO, ref is IORef.
Methods
newRef :: a -> m (ref a)Source
Create a new mutable variable holding the value supplied.
Return the current value stored in the mutable variable.
writeRef :: ref a -> a -> m ()Source
Write the supplied value into the mutable variable
atomicModifyRef :: ref a -> (a -> (a, b)) -> m bSource
Atomically modifies the contents of a mutable variable.
This function is useful for using mutable varibales in a safe way in a
multithreaded program. If you only have one mutable variable, then
using atomicModifyRef to access and modify it will prevent race
conditions.
Extending the atomicity to multiple mutable variables is problematic,
so it is recommended that if you need to do anything more complicated
then using MVar instead is a good idea.
atomicModifyRef does not apply the function strictly. This is
important to know even if all you are doing is replacing the value.
For example, this will leak memory:
ref <- newIORef 1 forever $ atomicModifyRef ref (\_ -> (2, ()))
Use atomicModifyRef' or atomicWriteRef to avoid this problem.
Instances
| (MonadLayer m, MonadMutVar ref (Inner m)) => MonadMutVar ref m | |
| MonadMutVar TVar STM | |
| MonadMutVar IORef IO | |
| (MonadMutVar ref f, MonadMutVar ref g) => MonadMutVar ref (Product f g) | |
| MonadMutVar (STRef s) (ST s) | |
| MonadMutVar (STRef s) (ST s) |
atomicModifyRef' :: MonadMutVar ref m => ref a -> (a -> (a, b)) -> m bSource
Strict version of atomicModifyRef. This forces both the value stored in
the mutable variable as well as the value returned.
atomicWriteRef :: MonadMutVar ref m => ref a -> a -> m ()Source
Variant of writeRef with the "barrier to reordering" property that
atomicModifyRef has.
modifyRef :: MonadMutVar ref m => ref a -> (a -> a) -> m ()Source
Mutate the contents of a mutable variable.
Be warned that modifyRef does not apply the function strictly. This means
if the program calls modifyRef many times, but seldomly uses the value,
thunks will pile up in memory resulting in a space leak. This is a common
mistake made when using a mutable varible as a counter. For example, the
following will likely produce a stack overflow:
ref <- newRef 0 replicateM_ 1000000 $ modifyRef ref (+1) readRef ref >>= print
To avoid this problem, use modifyRef' instead.
modifyRef' :: MonadMutVar ref m => ref a -> (a -> a) -> m ()Source
Strict version of modifyRef.