| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
GHC.Internal.STM
Contents
Synopsis
- newtype STM a = STM (State# RealWorld -> (# State# RealWorld, a #))
- atomically :: STM a -> IO a
- retry :: STM a
- orElse :: STM a -> STM a -> STM a
- throwSTM :: (HasCallStack, Exception e) => e -> STM a
- catchSTM :: Exception e => STM a -> (e -> STM a) -> STM a
- unsafeIOToSTM :: IO a -> STM a
- data TVar a = TVar (TVar# RealWorld a)
- newTVar :: a -> STM (TVar a)
- newTVarIO :: a -> IO (TVar a)
- readTVar :: TVar a -> STM a
- readTVarIO :: TVar a -> IO a
- writeTVar :: TVar a -> a -> STM ()
the STM monad
A monad supporting atomic memory transactions.
Instances
| Alternative STM Source # | Takes the first non- Since: base-4.8.0.0 |
| Applicative STM Source # | Since: base-4.8.0.0 |
| Functor STM Source # | Since: base-4.3.0.0 |
| Monad STM Source # | Since: base-4.3.0.0 |
| MonadPlus STM Source # | Takes the first non- Since: base-4.3.0.0 |
| Monoid a => Monoid (STM a) Source # | Since: base-4.17.0.0 |
| Semigroup a => Semigroup (STM a) Source # | Since: base-4.17.0.0 |
atomically :: STM a -> IO a Source #
Perform a series of STM actions atomically.
Using atomically inside an unsafePerformIO or unsafeInterleaveIO
subverts some of guarantees that STM provides. It makes it possible to
run a transaction inside of another transaction, depending on when the
thunk is evaluated. If a nested transaction is attempted, an exception
is thrown by the runtime. It is possible to safely use atomically inside
unsafePerformIO or unsafeInterleaveIO, but the typechecker does not
rule out programs that may attempt nested transactions, meaning that
the programmer must take special care to prevent these.
However, there are functions for creating transactional variables that
can always be safely called in unsafePerformIO. See: newTVarIO,
newTChanIO,
newBroadcastTChanIO,
newTQueueIO,
newTBQueueIO, and
newTMVarIO.
Using unsafePerformIO inside of atomically is also dangerous but for
different reasons. See unsafeIOToSTM for more on this.
Retry execution of the current memory transaction because it has seen
values in TVars which mean that it should not continue (e.g. the TVars
represent a shared buffer that is now empty). The implementation may
block the thread until one of the TVars that it has read from has been
updated. (GHC only)
throwSTM :: (HasCallStack, Exception e) => e -> STM a Source #
A variant of throw that can only be used within the STM monad.
Throwing an exception in STM aborts the transaction and propagates the
exception. If the exception is caught via catchSTM, only the changes
enclosed by the catch are rolled back; changes made outside of catchSTM
persist.
If the exception is not caught inside of the STM, it is re-thrown by
atomically, and the entire STM is rolled back.
Although throwSTM has a type that is an instance of the type of throw, the
two functions are subtly different:
throw e `seq` x ===> throw e throwSTM e `seq` x ===> x
The first example will cause the exception e to be raised,
whereas the second one won't. In fact, throwSTM will only cause
an exception to be raised when it is used within the STM monad.
The throwSTM variant should be used in preference to throw to
raise an exception within the STM monad because it guarantees
ordering with respect to other STM operations, whereas throw
does not.
unsafeIOToSTM :: IO a -> STM a Source #
Unsafely performs IO in the STM monad. Beware: this is a highly dangerous thing to do.
- The STM implementation will often run transactions multiple times, so you need to be prepared for this if your IO has any side effects.
- The STM implementation will abort transactions that are known to
be invalid and need to be restarted. This may happen in the middle
of
unsafeIOToSTM, so make sure you don't acquire any resources that need releasing (exception handlers are ignored when aborting the transaction). That includes doing any IO using Handles, for example. Getting this wrong will probably lead to random deadlocks. - The transaction may have seen an inconsistent view of memory when
the IO runs. Invariants that you expect to be true throughout
your program may not be true inside a transaction, due to the
way transactions are implemented. Normally this wouldn't be visible
to the programmer, but using
unsafeIOToSTMcan expose it.
TVars
Shared memory locations that support atomic memory transactions.
newTVarIO :: a -> IO (TVar a) Source #
IO version of newTVar. This is useful for creating top-level
TVars using unsafePerformIO, because using
atomically inside unsafePerformIO isn't
possible.
readTVarIO :: TVar a -> IO a Source #