Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- atomicallyNamed :: String -> STM a -> IO a
- atomically :: STM a -> IO a
- getSTMStats :: IO (Map String (Int, Int))
- dumpSTMStats :: IO ()
- registerDelay :: Int -> IO (TVar Bool)
- writeTVar :: TVar a -> a -> STM ()
- readTVar :: TVar a -> STM a
- readTVarIO :: TVar a -> IO a
- newTVarIO :: a -> IO (TVar a)
- newTVar :: a -> STM (TVar a)
- catchSTM :: Exception e => STM a -> (e -> STM a) -> STM a
- throwSTM :: Exception e => e -> STM a
- orElse :: STM a -> STM a -> STM a
- retry :: STM a
- data STM a
- data TVar a
- check :: Bool -> STM ()
- data TArray i e
- mkWeakTVar :: TVar a -> IO () -> IO (Weak (TVar a))
- swapTVar :: TVar a -> a -> STM a
- stateTVar :: TVar s -> (s -> (a, s)) -> STM a
- modifyTVar' :: TVar a -> (a -> a) -> STM ()
- modifyTVar :: TVar a -> (a -> a) -> STM ()
- isEmptyTQueue :: TQueue a -> STM Bool
- unGetTQueue :: TQueue a -> a -> STM ()
- tryPeekTQueue :: TQueue a -> STM (Maybe a)
- peekTQueue :: TQueue a -> STM a
- flushTQueue :: TQueue a -> STM [a]
- tryReadTQueue :: TQueue a -> STM (Maybe a)
- readTQueue :: TQueue a -> STM a
- writeTQueue :: TQueue a -> a -> STM ()
- newTQueueIO :: IO (TQueue a)
- newTQueue :: STM (TQueue a)
- data TQueue a
- mkWeakTMVar :: TMVar a -> IO () -> IO (Weak (TMVar a))
- isEmptyTMVar :: TMVar a -> STM Bool
- swapTMVar :: TMVar a -> a -> STM a
- tryReadTMVar :: TMVar a -> STM (Maybe a)
- readTMVar :: TMVar a -> STM a
- tryPutTMVar :: TMVar a -> a -> STM Bool
- putTMVar :: TMVar a -> a -> STM ()
- tryTakeTMVar :: TMVar a -> STM (Maybe a)
- takeTMVar :: TMVar a -> STM a
- newEmptyTMVarIO :: IO (TMVar a)
- newEmptyTMVar :: STM (TMVar a)
- newTMVarIO :: a -> IO (TMVar a)
- newTMVar :: a -> STM (TMVar a)
- data TMVar a
- cloneTChan :: TChan a -> STM (TChan a)
- isEmptyTChan :: TChan a -> STM Bool
- unGetTChan :: TChan a -> a -> STM ()
- dupTChan :: TChan a -> STM (TChan a)
- tryPeekTChan :: TChan a -> STM (Maybe a)
- peekTChan :: TChan a -> STM a
- tryReadTChan :: TChan a -> STM (Maybe a)
- readTChan :: TChan a -> STM a
- writeTChan :: TChan a -> a -> STM ()
- newBroadcastTChanIO :: IO (TChan a)
- newBroadcastTChan :: STM (TChan a)
- newTChanIO :: IO (TChan a)
- newTChan :: STM (TChan a)
- data TChan a
- isFullTBQueue :: TBQueue a -> STM Bool
- isEmptyTBQueue :: TBQueue a -> STM Bool
- lengthTBQueue :: TBQueue a -> STM Natural
- unGetTBQueue :: TBQueue a -> a -> STM ()
- tryPeekTBQueue :: TBQueue a -> STM (Maybe a)
- peekTBQueue :: TBQueue a -> STM a
- flushTBQueue :: TBQueue a -> STM [a]
- tryReadTBQueue :: TBQueue a -> STM (Maybe a)
- readTBQueue :: TBQueue a -> STM a
- writeTBQueue :: TBQueue a -> a -> STM ()
- newTBQueueIO :: Natural -> IO (TBQueue a)
- newTBQueue :: Natural -> STM (TBQueue a)
- data TBQueue a
Documentation
atomically :: STM a -> IO a Source #
dumpSTMStats :: IO () Source #
registerDelay :: Int -> IO (TVar Bool) #
Switch the value of returned TVar
from initial value False
to True
after a given number of microseconds. The caveats associated with
threadDelay
also apply.
readTVarIO :: TVar a -> IO a #
newTVarIO :: a -> IO (TVar a) #
IO
version of newTVar
. This is useful for creating top-level
TVar
s using unsafePerformIO
, because using
atomically
inside unsafePerformIO
isn't
possible.
throwSTM :: Exception e => e -> STM a #
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.
Retry execution of the current memory transaction because it has seen
values in TVar
s which mean that it should not continue (e.g. the TVar
s
represent a shared buffer that is now empty). The implementation may
block the thread until one of the TVar
s that it has read from has been
updated. (GHC only)
A monad supporting atomic memory transactions.
Instances
Shared memory locations that support atomic memory transactions.
Check that the boolean condition is true and, if not, retry
.
In other words, check b = unless b retry
.
Since: stm-2.1.1
TArray is a transactional array, supporting the usual MArray
interface for mutable arrays.
It is currently implemented as Array ix (TVar e)
,
but it may be replaced by a more efficient implementation in the future
(the interface will remain the same, however).
Instances
MArray TArray e STM | |
Defined in Control.Concurrent.STM.TArray getBounds :: Ix i => TArray i e -> STM (i, i) # getNumElements :: Ix i => TArray i e -> STM Int newArray :: Ix i => (i, i) -> e -> STM (TArray i e) # newArray_ :: Ix i => (i, i) -> STM (TArray i e) # unsafeNewArray_ :: Ix i => (i, i) -> STM (TArray i e) unsafeRead :: Ix i => TArray i e -> Int -> STM e unsafeWrite :: Ix i => TArray i e -> Int -> e -> STM () | |
Ix i => Eq (TArray i e) | |
stateTVar :: TVar s -> (s -> (a, s)) -> STM a #
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: stm-2.5.0
modifyTVar' :: TVar a -> (a -> a) -> STM () #
Strict version of modifyTVar
.
Since: stm-2.3
modifyTVar :: TVar a -> (a -> a) -> STM () #
Mutate the contents of a TVar
. N.B., this version is
non-strict.
Since: stm-2.3
unGetTQueue :: TQueue a -> a -> STM () #
Put a data item back onto a channel, where it will be the next item read.
tryPeekTQueue :: TQueue a -> STM (Maybe a) #
A version of peekTQueue
which does not retry. Instead it
returns Nothing
if no value is available.
peekTQueue :: TQueue a -> STM a #
Get the next value from the TQueue
without removing it,
retrying if the channel is empty.
flushTQueue :: TQueue a -> STM [a] #
Efficiently read the entire contents of a TQueue
into a list. This
function never retries.
Since: stm-2.4.5
tryReadTQueue :: TQueue a -> STM (Maybe a) #
A version of readTQueue
which does not retry. Instead it
returns Nothing
if no value is available.
readTQueue :: TQueue a -> STM a #
Read the next value from the TQueue
.
writeTQueue :: TQueue a -> a -> STM () #
Write a value to a TQueue
.
newTQueueIO :: IO (TQueue a) #
IO
version of newTQueue
. This is useful for creating top-level
TQueue
s using unsafePerformIO
, because using
atomically
inside unsafePerformIO
isn't
possible.
TQueue
is an abstract type representing an unbounded FIFO channel.
Since: stm-2.4
tryReadTMVar :: TMVar a -> STM (Maybe a) #
A version of readTMVar
which does not retry. Instead it
returns Nothing
if no value is available.
Since: stm-2.3
tryPutTMVar :: TMVar a -> a -> STM Bool #
tryTakeTMVar :: TMVar a -> STM (Maybe a) #
A version of takeTMVar
that does not retry
. The tryTakeTMVar
function returns Nothing
if the TMVar
was empty, or
if
the Just
aTMVar
was full with contents a
. After tryTakeTMVar
, the
TMVar
is left empty.
newEmptyTMVarIO :: IO (TMVar a) #
IO
version of newEmptyTMVar
. This is useful for creating top-level
TMVar
s using unsafePerformIO
, because using
atomically
inside unsafePerformIO
isn't
possible.
newEmptyTMVar :: STM (TMVar a) #
Create a TMVar
which is initially empty.
newTMVarIO :: a -> IO (TMVar a) #
IO
version of newTMVar
. This is useful for creating top-level
TMVar
s using unsafePerformIO
, because using
atomically
inside unsafePerformIO
isn't
possible.
A TMVar
is a synchronising variable, used
for communication between concurrent threads. It can be thought of
as a box, which may be empty or full.
cloneTChan :: TChan a -> STM (TChan a) #
Clone a TChan
: similar to dupTChan, but the cloned channel starts with the
same content available as the original channel.
Since: stm-2.4
unGetTChan :: TChan a -> a -> STM () #
Put a data item back onto a channel, where it will be the next item read.
dupTChan :: TChan a -> STM (TChan a) #
Duplicate a TChan
: the duplicate channel begins empty, but data written to
either channel from then on will be available from both. Hence this creates
a kind of broadcast channel, where data written by anyone is seen by
everyone else.
tryPeekTChan :: TChan a -> STM (Maybe a) #
A version of peekTChan
which does not retry. Instead it
returns Nothing
if no value is available.
Since: stm-2.3
peekTChan :: TChan a -> STM a #
Get the next value from the TChan
without removing it,
retrying if the channel is empty.
Since: stm-2.3
tryReadTChan :: TChan a -> STM (Maybe a) #
A version of readTChan
which does not retry. Instead it
returns Nothing
if no value is available.
Since: stm-2.3
writeTChan :: TChan a -> a -> STM () #
Write a value to a TChan
.
newBroadcastTChanIO :: IO (TChan a) #
IO
version of newBroadcastTChan
.
Since: stm-2.4
newBroadcastTChan :: STM (TChan a) #
Create a write-only TChan
. More precisely, readTChan
will retry
even after items have been written to the channel. The only way to read
a broadcast channel is to duplicate it with dupTChan
.
Consider a server that broadcasts messages to clients:
serve :: TChan Message -> Client -> IO loop serve broadcastChan client = do myChan <- dupTChan broadcastChan forever $ do message <- readTChan myChan send client message
The problem with using newTChan
to create the broadcast channel is that if
it is only written to and never read, items will pile up in memory. By
using newBroadcastTChan
to create the broadcast channel, items can be
garbage collected after clients have seen them.
Since: stm-2.4
newTChanIO :: IO (TChan a) #
IO
version of newTChan
. This is useful for creating top-level
TChan
s using unsafePerformIO
, because using
atomically
inside unsafePerformIO
isn't
possible.
TChan
is an abstract type representing an unbounded FIFO channel.
isFullTBQueue :: TBQueue a -> STM Bool #
unGetTBQueue :: TBQueue a -> a -> STM () #
Put a data item back onto a channel, where it will be the next item read. Blocks if the queue is full.
tryPeekTBQueue :: TBQueue a -> STM (Maybe a) #
A version of peekTBQueue
which does not retry. Instead it
returns Nothing
if no value is available.
peekTBQueue :: TBQueue a -> STM a #
Get the next value from the TBQueue
without removing it,
retrying if the channel is empty.
flushTBQueue :: TBQueue a -> STM [a] #
Efficiently read the entire contents of a TBQueue
into a list. This
function never retries.
Since: stm-2.4.5
tryReadTBQueue :: TBQueue a -> STM (Maybe a) #
A version of readTBQueue
which does not retry. Instead it
returns Nothing
if no value is available.
readTBQueue :: TBQueue a -> STM a #
Read the next value from the TBQueue
.
writeTBQueue :: TBQueue a -> a -> STM () #
Write a value to a TBQueue
; blocks if the queue is full.
newTBQueueIO :: Natural -> IO (TBQueue a) #
IO
version of newTBQueue
. This is useful for creating top-level
TBQueue
s using unsafePerformIO
, because using
atomically
inside unsafePerformIO
isn't
possible.
Builds and returns a new instance of TBQueue
.