Safe Haskell | None |
---|---|
Language | Haskell2010 |
- installService :: Node -> t -> [Char] -> TransIO ()
- beamTo :: Node -> TransientIO ()
- forkTo :: Node -> TransientIO ()
- callTo :: Loggable a => Node -> TransIO a -> TransIO a
- runAt :: Loggable a => Node -> TransIO a -> TransIO a
- streamFrom :: Loggable a => Node -> TransIO (StreamData a) -> TransIO (StreamData a)
- callTo' :: (Show a, Read a, Typeable a) => Node -> TransIO a -> TransIO a
- type Blocked = MVar ()
- type BuffSize = Int
- data Connection = Connection (Maybe (PortID, Handle, Socket, Blocked)) BuffSize
- setBufSize :: Int -> TransIO ()
- readHandler :: Read a => Handle -> IO (StreamData a)
- connectTo' :: Int -> HostName -> PortID -> IO Handle
- listen :: Node -> TransIO ()
- beamInit :: Node -> TransIO a -> IO a
- data Pool = Pool {}
- data Node = Node {}
- release :: MonadIO m => Node -> Handle -> m ()
- assign :: MonadIO m => Int -> Node -> m Handle
- emptyPool :: MonadIO m => m (IORef Pool)
- createNode :: HostName -> Integer -> Node
- nodeList :: TVar [Node]
- myNode :: IORef (Maybe a)
- setMyNode :: MonadIO m => a -> m ()
- getMyNode :: TransIO x
- getNodes :: MonadIO m => m [Node]
- addNodes :: MonadIO m => [Node] -> m ()
- shuffleNodes :: MonadIO m => m [Node]
- clustered :: Loggable a => TransIO a -> TransIO a
- clustered' :: (Read b, Show b, Typeable * b) => TransIO b -> TransientIO [b]
- mclustered :: (Monoid a, Loggable a) => TransIO a -> TransIO a
- connect :: Node -> Node -> TransientIO ()
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
streamFrom :: Loggable a => Node -> TransIO (StreamData a) -> TransIO (StreamData a) Source
callTo' :: (Show a, Read a, Typeable a) => Node -> TransIO a -> TransIO a Source
A connectionless version of callTo for long running remote calls
data Connection Source
setBufSize :: Int -> TransIO () Source
readHandler :: Read a => Handle -> IO (StreamData a) 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.
Level 2: connections node lists and operations with the node list
createNode :: HostName -> Integer -> Node Source
shuffleNodes :: MonadIO m => m [Node] 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