-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Software Transactional Memory -- -- A modular composable concurrency abstraction. @package stm @version 2.4.4.1 -- | TBQueue is a bounded version of TQueue. The queue has -- a maximum capacity set when it is created. If the queue already -- contains the maximum number of elements, then writeTBQueue -- blocks until an element is removed from the queue. -- -- The implementation is based on the traditional purely-functional queue -- representation that uses two lists to obtain amortised O(1) -- enqueue and dequeue operations. module Control.Concurrent.STM.TBQueue -- | TBQueue is an abstract type representing a bounded FIFO -- channel. data TBQueue a -- | Build and returns a new instance of TBQueue newTBQueue :: Int -> STM (TBQueue a) -- | IO version of newTBQueue. This is useful for creating -- top-level TBQueues using unsafePerformIO, because using -- atomically inside unsafePerformIO isn't possible. newTBQueueIO :: Int -> IO (TBQueue a) -- | Read the next value from the TBQueue. readTBQueue :: TBQueue a -> STM a -- | A version of readTBQueue which does not retry. Instead it -- returns Nothing if no value is available. tryReadTBQueue :: TBQueue a -> STM (Maybe a) -- | Get the next value from the TBQueue without removing it, -- retrying if the channel is empty. peekTBQueue :: TBQueue a -> STM a -- | A version of peekTBQueue which does not retry. Instead it -- returns Nothing if no value is available. tryPeekTBQueue :: TBQueue a -> STM (Maybe a) -- | Write a value to a TBQueue; blocks if the queue is full. writeTBQueue :: 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. unGetTBQueue :: TBQueue a -> a -> STM () -- | Returns True if the supplied TBQueue is empty. isEmptyTBQueue :: TBQueue a -> STM Bool -- | Returns True if the supplied TBQueue is full. isFullTBQueue :: TBQueue a -> STM Bool instance GHC.Classes.Eq (Control.Concurrent.STM.TBQueue.TBQueue a) -- | A TQueue is like a TChan, with two important -- differences: -- -- -- -- The implementation is based on the traditional purely-functional queue -- representation that uses two lists to obtain amortised O(1) -- enqueue and dequeue operations. module Control.Concurrent.STM.TQueue -- | TQueue is an abstract type representing an unbounded FIFO -- channel. data TQueue a -- | Build and returns a new instance of TQueue newTQueue :: STM (TQueue a) -- | IO version of newTQueue. This is useful for creating -- top-level TQueues using unsafePerformIO, because using -- atomically inside unsafePerformIO isn't possible. newTQueueIO :: IO (TQueue a) -- | Read the next value from the TQueue. readTQueue :: TQueue a -> STM a -- | A version of readTQueue which does not retry. Instead it -- returns Nothing if no value is available. tryReadTQueue :: TQueue a -> STM (Maybe a) -- | Get the next value from the TQueue without removing it, -- retrying if the channel is empty. peekTQueue :: TQueue a -> STM a -- | A version of peekTQueue which does not retry. Instead it -- returns Nothing if no value is available. tryPeekTQueue :: TQueue a -> STM (Maybe a) -- | Write a value to a TQueue. writeTQueue :: TQueue a -> a -> STM () -- | Put a data item back onto a channel, where it will be the next item -- read. unGetTQueue :: TQueue a -> a -> STM () -- | Returns True if the supplied TQueue is empty. isEmptyTQueue :: TQueue a -> STM Bool instance GHC.Classes.Eq (Control.Concurrent.STM.TQueue.TQueue a) -- | TChan: Transactional channels (GHC only) module Control.Concurrent.STM.TChan -- | TChan is an abstract type representing an unbounded FIFO -- channel. data TChan a -- | Build and return a new instance of TChan newTChan :: STM (TChan a) -- | IO version of newTChan. This is useful for creating -- top-level TChans using unsafePerformIO, because using -- atomically inside unsafePerformIO isn't possible. newTChanIO :: IO (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. newBroadcastTChan :: STM (TChan a) -- | IO version of newBroadcastTChan. newBroadcastTChanIO :: IO (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. dupTChan :: 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. cloneTChan :: TChan a -> STM (TChan a) -- | Read the next value from the TChan. readTChan :: TChan a -> STM a -- | A version of readTChan which does not retry. Instead it returns -- Nothing if no value is available. tryReadTChan :: TChan a -> STM (Maybe a) -- | Get the next value from the TChan without removing it, -- retrying if the channel is empty. peekTChan :: TChan a -> STM a -- | A version of peekTChan which does not retry. Instead it returns -- Nothing if no value is available. tryPeekTChan :: TChan a -> STM (Maybe a) -- | Write a value to a TChan. writeTChan :: TChan a -> a -> STM () -- | Put a data item back onto a channel, where it will be the next item -- read. unGetTChan :: TChan a -> a -> STM () -- | Returns True if the supplied TChan is empty. isEmptyTChan :: TChan a -> STM Bool instance GHC.Classes.Eq (Control.Concurrent.STM.TChan.TChan a) -- | TMVar: Transactional MVars, for use in the STM monad (GHC only) module Control.Concurrent.STM.TMVar -- | 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. data TMVar a -- | Create a TMVar which contains the supplied value. newTMVar :: a -> STM (TMVar a) -- | Create a TMVar which is initially empty. newEmptyTMVar :: STM (TMVar a) -- | IO version of newTMVar. This is useful for creating -- top-level TMVars using unsafePerformIO, because using -- atomically inside unsafePerformIO isn't possible. newTMVarIO :: a -> IO (TMVar a) -- | IO version of newEmptyTMVar. This is useful for -- creating top-level TMVars using unsafePerformIO, because -- using atomically inside unsafePerformIO isn't possible. newEmptyTMVarIO :: IO (TMVar a) -- | Return the contents of the TMVar. If the TMVar is -- currently empty, the transaction will retry. After a -- takeTMVar, the TMVar is left empty. takeTMVar :: TMVar a -> STM a -- | Put a value into a TMVar. If the TMVar is currently -- full, putTMVar will retry. putTMVar :: TMVar a -> a -> STM () -- | This is a combination of takeTMVar and putTMVar; ie. it -- takes the value from the TMVar, puts it back, and also returns -- it. readTMVar :: TMVar a -> STM a -- | A version of readTMVar which does not retry. Instead it returns -- Nothing if no value is available. tryReadTMVar :: TMVar a -> STM (Maybe a) -- | Swap the contents of a TMVar for a new value. swapTMVar :: TMVar a -> a -> STM a -- | A version of takeTMVar that does not retry. The -- tryTakeTMVar function returns Nothing if the -- TMVar was empty, or Just a if the TMVar -- was full with contents a. After tryTakeTMVar, the -- TMVar is left empty. tryTakeTMVar :: TMVar a -> STM (Maybe a) -- | A version of putTMVar that does not retry. The -- tryPutTMVar function attempts to put the value a into -- the TMVar, returning True if it was successful, or -- False otherwise. tryPutTMVar :: TMVar a -> a -> STM Bool -- | Check whether a given TMVar is empty. isEmptyTMVar :: TMVar a -> STM Bool -- | Make a Weak pointer to a TMVar, using the second -- argument as a finalizer to run when the TMVar is -- garbage-collected. mkWeakTMVar :: TMVar a -> IO () -> IO (Weak (TMVar a)) instance GHC.Classes.Eq (Control.Concurrent.STM.TMVar.TMVar a) -- | TVar: Transactional variables module Control.Concurrent.STM.TVar -- | Shared memory locations that support atomic memory transactions. data TVar a :: * -> * -- | Create a new TVar holding a value supplied newTVar :: a -> STM (TVar a) -- | IO version of newTVar. This is useful for creating -- top-level TVars using unsafePerformIO, because using -- atomically inside unsafePerformIO isn't possible. newTVarIO :: a -> IO (TVar a) -- | Return the current value stored in a TVar readTVar :: TVar a -> STM a -- | Return the current value stored in a TVar. This is equivalent to -- --
--   readTVarIO = atomically . readTVar
--   
-- -- but works much faster, because it doesn't perform a complete -- transaction, it just reads the current value of the TVar. readTVarIO :: TVar a -> IO a -- | Write the supplied value into a TVar writeTVar :: TVar a -> a -> STM () -- | Mutate the contents of a TVar. N.B., this version is -- non-strict. modifyTVar :: TVar a -> (a -> a) -> STM () -- | Strict version of modifyTVar. modifyTVar' :: TVar a -> (a -> a) -> STM () -- | Swap the contents of a TVar for a new value. swapTVar :: TVar a -> a -> STM a -- | Set the value of returned TVar to True after a given number of -- microseconds. The caveats associated with threadDelay also apply. registerDelay :: Int -> IO (TVar Bool) -- | Make a Weak pointer to a TVar, using the second argument -- as a finalizer to run when TVar is garbage-collected mkWeakTVar :: TVar a -> IO () -> IO (Weak (TVar a)) -- | TArrays: transactional arrays, for use in the STM monad module Control.Concurrent.STM.TArray -- | 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). data TArray i e instance GHC.Arr.Ix i => GHC.Classes.Eq (Control.Concurrent.STM.TArray.TArray i e) instance Data.Array.Base.MArray Control.Concurrent.STM.TArray.TArray e GHC.Conc.Sync.STM -- | 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). module Control.Monad.STM -- | A monad supporting atomic memory transactions. data STM a :: * -> * -- | Perform a series of STM actions atomically. -- -- You cannot use atomically inside an unsafePerformIO or -- unsafeInterleaveIO. Any attempt to do so will result in a -- runtime error. (Reason: allowing this would effectively allow a -- transaction inside a transaction, depending on exactly when the thunk -- is evaluated.) -- -- However, see newTVarIO, which can be called inside -- unsafePerformIO, and which allows top-level TVars to be -- allocated. atomically :: STM a -> IO a -- | always is a variant of alwaysSucceeds in which the invariant is -- expressed as an STM Bool action that must return True. Returning False -- or raising an exception are both treated as invariant failures. always :: STM Bool -> STM () -- | alwaysSucceeds adds a new invariant that must be true when passed to -- alwaysSucceeds, at the end of the current transaction, and at the end -- of every subsequent transaction. If it fails at any of those points -- then the transaction violating it is aborted and the exception raised -- by the invariant is propagated. alwaysSucceeds :: STM a -> STM () -- | 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 -- udpated. (GHC only) retry :: STM a -- | Compose two alternative STM actions (GHC only). If the first action -- completes without retrying then it forms the result of the orElse. -- Otherwise, if the first action retries, then the second action is -- tried in its place. If both actions retry then the orElse as a whole -- retries. orElse :: STM a -> STM a -> STM a check :: Bool -> STM () -- | 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. -- -- 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. throwSTM :: Exception e => e -> STM a -- | Exception handling within STM actions. catchSTM :: Exception e => STM a -> (e -> STM a) -> STM a instance Control.Monad.Fix.MonadFix GHC.Conc.Sync.STM -- | Software Transactional Memory: a modular composable concurrency -- abstraction. See -- -- module Control.Concurrent.STM -- | TSem: transactional semaphores. module Control.Concurrent.STM.TSem -- | TSem is a transactional semaphore. It holds a certain number of -- units, and units may be acquired or released by waitTSem and -- signalTSem respectively. When the TSem is empty, -- waitTSem blocks. -- -- Note that TSem has no concept of fairness, and there is no -- guarantee that threads blocked in waitTSem will be unblocked in -- the same order; in fact they will all be unblocked at the same time -- and will fight over the TSem. Hence TSem is not suitable -- if you expect there to be a high number of threads contending for the -- resource. However, like other STM abstractions, TSem is -- composable. data TSem newTSem :: Int -> STM TSem waitTSem :: TSem -> STM () signalTSem :: TSem -> STM () instance GHC.Classes.Eq Control.Concurrent.STM.TSem.TSem