| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Control.Concurrent.Process.StoredMVar
Description
This module is an adaptation of MVar to an
   interprocess communication (IPC).
   The IPC setting implies a few changes to the interface.
StoredMVarresides in a shared memory region.- We use 
Storableinstance to serialize and deserialize a value. - Point (2) implies the value is always fully evaluated before being stored.
 - Scheduling is done by OS, thus the module does not guarantee FIFO order.
 - Using 
StoredMVaris only safe ifStorableinstance for its content is correct andpeekdoes not throw exceptions. Ifpeekthrows an exception insidetakeMVarorswapMVar, the original content ofStoredMVaris not restored 
Synopsis
- data StoredMVar a
 - mVarName :: StoredMVar a -> SOName (StoredMVar a)
 - newEmptyMVar :: forall a. Storable a => IO (StoredMVar a)
 - newMVar :: Storable a => a -> IO (StoredMVar a)
 - lookupMVar :: Storable a => SOName (StoredMVar a) -> IO (StoredMVar a)
 - takeMVar :: Storable a => StoredMVar a -> IO a
 - putMVar :: Storable a => StoredMVar a -> a -> IO ()
 - readMVar :: Storable a => StoredMVar a -> IO a
 - swapMVar :: Storable a => StoredMVar a -> a -> IO a
 - tryTakeMVar :: Storable a => StoredMVar a -> IO (Maybe a)
 - tryPutMVar :: Storable a => StoredMVar a -> a -> IO Bool
 - tryReadMVar :: Storable a => StoredMVar a -> IO (Maybe a)
 - trySwapMVar :: Storable a => StoredMVar a -> a -> IO (Maybe a)
 - isEmptyMVar :: StoredMVar a -> IO Bool
 - withMVar :: Storable a => StoredMVar a -> (a -> IO b) -> IO b
 - withMVarMasked :: Storable a => StoredMVar a -> (a -> IO b) -> IO b
 - modifyMVar :: Storable a => StoredMVar a -> (a -> IO (a, b)) -> IO b
 - modifyMVar_ :: Storable a => StoredMVar a -> (a -> IO a) -> IO ()
 - modifyMVarMasked :: Storable a => StoredMVar a -> (a -> IO (a, b)) -> IO b
 - modifyMVarMasked_ :: Storable a => StoredMVar a -> (a -> IO a) -> IO ()
 
Documentation
data StoredMVar a Source #
An StoredMVar is a synchronising variable, used
   for communication between concurrent processes or threads.
   It can be thought of as a a box, which may be empty or full.
StoredMVar tries to mimic vanilla MVar, though it behaves quite differently.
   It uses Storable instance to make the value accessible in different memory spaces.
   Thus, the content of StoredMVar is forced to be fully evaluated and serialized.
Instances
| Eq (StoredMVar a) Source # | |
Defined in Control.Concurrent.Process.StoredMVar  | |
mVarName :: StoredMVar a -> SOName (StoredMVar a) Source #
Get a global reference to the StoredMVar.
   Send this reference to another process to lookup this StoredMVar and
   start interprocess communication.
newEmptyMVar :: forall a. Storable a => IO (StoredMVar a) Source #
Create a StoredMVar which is initially empty.
newMVar :: Storable a => a -> IO (StoredMVar a) Source #
Create a StoredMVar which is initially empty.
lookupMVar :: Storable a => SOName (StoredMVar a) -> IO (StoredMVar a) Source #
Find a StoredMVar created in another process ot thread by its reference.
takeMVar :: Storable a => StoredMVar a -> IO a Source #
Return the contents of the StoredMVar.  If the StoredMVar is currently
   empty, takeMVar will wait until it is full.  After a takeMVar,
   the StoredMVar is left empty.
takeMVaris single-wakeup. That is, if there are multiple processes blocked intakeMVar, and theStoredMVarbecomes full, only one thread will be woken up.- The library makes no guarantees about the order in which processes are woken up. This is all up to implementation-dependent OS scheduling.
 
putMVar :: Storable a => StoredMVar a -> a -> IO () Source #
Put a value into an StoredMVar.  If the StoredMVar is currently full,
   putMVar will wait until it becomes empty.
putMVaris single-wakeup. That is, if there are multiple threads or processes blocked inputMVar, and theStoredMVarbecomes empty, only one thread will be woken up.- The library makes no guarantees about the order in which processes are woken up. This is all up to implementation-dependent OS scheduling.
 
readMVar :: Storable a => StoredMVar a -> IO a Source #
Atomically read the contents of an StoredMVar.  If the StoredMVar is
   currently empty, readMVar will wait until its full.
   readMVar is guaranteed to receive the next putMVar.
readMVar is multiple-wakeup, so when multiple readers are
    blocked on an StoredMVar, all of them are woken up at the same time.
swapMVar :: Storable a => StoredMVar a -> a -> IO a Source #
Atomically take a value from an StoredMVar, put a new value into the StoredMVar and
   return the value taken.
tryTakeMVar :: Storable a => StoredMVar a -> IO (Maybe a) Source #
A non-blocking version of takeMVar.  The tryTakeMVar function
   returns immediately, with Nothing if the StoredMVar was empty, or
    if the Just aStoredMVar was full with contents a.
   After tryTakeMVar, the StoredMVar is left empty.
tryPutMVar :: Storable a => StoredMVar a -> a -> IO Bool Source #
A non-blocking version of putMVar.
   The tryPutMVar function
   attempts to put the value a into the StoredMVar, returning True if
   it was successful, or False otherwise.
tryReadMVar :: Storable a => StoredMVar a -> IO (Maybe a) Source #
A non-blocking version of readMVar.
   The tryReadMVar function
   returns immediately, with Nothing if the StoredMVar was empty, or
    if the Just aStoredMVar was full with contents a.
trySwapMVar :: Storable a => StoredMVar a -> a -> IO (Maybe a) Source #
A non-blocking version of swapMVar.
   Atomically attempt take a value from an StoredMVar, put a new value into the StoredMVar and
   return the value taken (thus, leave the StoredMVar full).
   Return Nothing if the StoredMVar was empty (and leave it empty).
isEmptyMVar :: StoredMVar a -> IO Bool Source #
Check whether a given StoredMVar is empty.
Notice that the boolean value returned  is just a snapshot of
   the state of the MVar. By the time you get to react on its result,
   the MVar may have been filled (or emptied) - so be extremely
   careful when using this operation.  Use tryTakeMVar instead if possible.
withMVar :: Storable a => StoredMVar a -> (a -> IO b) -> IO b Source #
withMVar is an exception-safe wrapper for operating on the contents
   of an StoredMVar.  This operation is exception-safe: it will replace the
   original contents of the StoredMVar if an exception is raised (see
   Control.Exception).  However, it is only atomic if there are no
  other producers for this StoredMVar.
withMVarMasked :: Storable a => StoredMVar a -> (a -> IO b) -> IO b Source #
Like withMVar, but the IO action in the second argument is executed
   with asynchronous exceptions masked.
modifyMVar :: Storable a => StoredMVar a -> (a -> IO (a, b)) -> IO b Source #
A slight variation on modifyMVar_ that allows a value to be
   returned (b) in addition to the modified value of the StoredMVar.
modifyMVar_ :: Storable a => StoredMVar a -> (a -> IO a) -> IO () Source #
An exception-safe wrapper for modifying the contents of an StoredMVar.
   Like withMVar, modifyMVar will replace the original contents of
   the StoredMVar if an exception is raised during the operation.  This
   function is only atomic if there are no other producers for this
   StoredMVar.
modifyMVarMasked :: Storable a => StoredMVar a -> (a -> IO (a, b)) -> IO b Source #
Like modifyMVar, but the IO action in the second argument is executed with
   asynchronous exceptions masked.
modifyMVarMasked_ :: Storable a => StoredMVar a -> (a -> IO a) -> IO () Source #
Like modifyMVar_, but the IO action in the second argument is executed with
   asynchronous exceptions masked.