DSTM-0.1.1: A framework for using STM within distributed systems

Control.Distributed.STM.DSTM

Synopsis

Documentation

data TVar a Source

Shared memory locations that support atomic memory transactions. Between different nodes memory is shared using transparent process communication. (TVars are called host TVars when they reside on the process where they have been created by calling newTVar. They are called link TVars on other processes)

Instances

Read (TVar a) 
Show (TVar a) 
Dist a => Dist (TVar a) 

data STM a Source

A monad supporting atomic memory transactions

Instances

newTVar :: Dist a => a -> STM (TVar a)Source

Create a new TVar holding a value supplied

readTVar :: Dist a => TVar a -> STM aSource

Return the current value stored in a TVar

writeTVar :: Dist a => TVar a -> a -> STM ()Source

Write the supplied value into a TVar

atomic :: Show a => STM a -> IO aSource

Perform a series of STM actions atomically

retry :: STM aSource

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.

orElse :: STM a -> STM a -> STM aSource

Compose two alternative STM actions. 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

throw :: SomeException -> STM aSource

Throw an exception within an STM action

catch :: STM a -> (SomeException -> STM a) -> STM aSource

Exception handling within STM actions

class (Show a, Read a) => Dist a whereSource

The class Dist defines the distribution property of TVar values. Any TVar value must implement class Dist. All basic data types exported by the Prelude are instances of Dist, and Dist may be derived for any data type whose constituents are also instances of Dist. Any custom-typed TVar value type should implement finTVars and regTVars to do nothing and return '()'.

Note that finTVars and regTVars should never be called by the application itself!

Methods

regTVars :: EnvAddr -> a -> IO ()Source

Do not call regTVars yourself!

regTVars registers all TVars within a with a host TVar link count before the TVars in a are sent to remote nodes

finTVars :: a -> IO ()Source

Do not call finTVars yourself!

finTVars installs finalizers at all link TVars in a which send messages to their host TVars to remove them from the host TVar link count after the link TVars have been garbage collected

Instances

Dist Bool 
Dist Char 
Dist Float 
Dist Int 
Dist Integer 
Dist () 
Dist a => Dist [a] 
Dist a => Dist (Maybe a) 
Dist a => Dist (TVar a) 
(Dist a, Dist b) => Dist (Either a b) 
(Dist a, Dist b) => Dist (a, b) 
(Dist a, Dist b, Dist c) => Dist (a, b, c) 
(Dist a, Dist b, Dist c, Dist d) => Dist (a, b, c, d) 

gDefaultNameServer :: StringSource

The default name server for the process running the main function. Usually it is localhost.

registerTVar :: Dist a => String -> TVar a -> String -> IO ()Source

registerTVar server tVar name registers tVar with name onto server

deregisterTVar :: String -> String -> IO ()Source

deregisterTVar server name removes name from server

lookupTVar :: forall a. Dist a => String -> String -> IO (Maybe (TVar a))Source

lookupTVar server name returns (Just tVar) if a tVar registration of name exists on server, Nothing otherwise.

startDistSource

Arguments

:: IO ()

application main function to be executed. Each main function in the distributed system has to be wrapped in a startDist call

-> IO () 

startDist enables inter process communication and exception handling and then executes the given main function

data SomeDistTVarException Source

SomeDistTVarException is the abstract exception type which is thrown by the DSTM library when either readTVar or writeTVar is called on an unreachable TVar. A TVar becomes unreachable when the process hosting the TVar becomes unreachable. An atomic transaction using a TVar which becomes unreachable during the execution of atomic may either execute completely (without the unreachable TVar(s)) or execute not at all depending on transaction states. In either case an exception of type SomeDistTVarException is raised.

isDistErrTVar :: SomeDistTVarException -> TVar a -> BoolSource

isDistErrTVar e tVar checks whether tVar is unreachable when exception e had been raised. It returns True if the exception raised denotes tVar as unreachable, False otherwise. A TVar returning True once will never return a False check result.