transient-0.1.0.8: A monad for extensible effects and primitives for unrestricted composability of applications

Safe HaskellNone
LanguageHaskell2010

Transient.Move

Contents

Description

Synopsis

Documentation

installService :: Node -> t -> [Char] -> TransIO () Source

install in a remote node a haskell package with an executable transient service initialized with listen the package, the git repository and the main exectable must have the same name

beamTo :: Node -> TransientIO () Source

continue the execution in a new node all the previous actions from listen to this statement must have been logged

forkTo :: Node -> TransientIO () Source

execute in the remote node a process with the same execution state all the previous actions from listen to this statement must have been logged

callTo :: Loggable a => Node -> TransIO a -> TransIO a Source

executes an action in another node. All the previous actions from listen to this statement must have been logged

runAt :: Loggable a => Node -> TransIO a -> TransIO a Source

synonymous of callTo all the previous actions from listen to this statement must have been logged

streamFrom :: Loggable a => Node -> TransIO (StreamData a) -> TransIO (StreamData a) Source

callTo can stream data but can not inform the receiving process about the finalization. This call does it.

All the previous actions from listen to this statement must have been logged

callTo' :: (Show a, Read a, Typeable a) => Node -> TransIO a -> TransIO a Source

A connectionless version of callTo for long running remote calls

type Blocked = MVar () Source

listen :: Node -> TransIO () Source

Wait for messages and replay the rest of the monadic sequence with the log received.

beamInit :: Node -> TransIO a -> IO a Source

init a Transient process in a interactive as well as in a replay mode. It is intended for twin processes that interact among them in different nodes.

data Pool Source

Constructors

Pool 

Fields

free :: [Handle]
 
pending :: Int
 

data Node Source

Constructors

Node 

release :: MonadIO m => Node -> Handle -> m () Source

Level 2: connections node lists and operations with the node list

setMyNode :: MonadIO m => a -> m () Source

addNodes :: MonadIO m => [Node] -> m () Source

clustered :: Loggable a => TransIO a -> TransIO a Source

execute a Transient action in each of the nodes connected.

The response of each node is returned and processed by the rest of the procedure. By default, the response is processed in a new thread. To restrict the number of threads use the thread control primitives.

this snippet receive a message from each of the simulated nodes: > main = keep $ do > let nodes= map createLocalNode [2000..2005] > addNodes nodes > (foldl (|) empty $ map listen nodes) | return () > > r <- clustered $ do > Connection (Just(PortNumber port, _, _, _)) _ <- getSData > return $ "hi from " ++ show port++ "n" > liftIO $ putStrLn r > where > createLocalNode n= createNode "localhost" (PortNumber n)

clustered' :: (Read b, Show b, Typeable * b) => TransIO b -> TransientIO [b] Source

a connectionless version of clustered for long running remote computations. Not tested

connect :: Node -> Node -> TransientIO () Source

Initiates the transient monad, initialize it as a new node (first parameter) and connect it to an existing node (second parameter). The other node will notify about this connection to all the nodes connected to him. this new connected node will receive the list of nodes the local list of nodes then is updated with this list. it can be retrieved with getNodes