distributed-process-simplelocalnet-0.2.3.2: Simple zero-configuration backend for Cloud Haskell

Safe HaskellNone
LanguageHaskell98

Control.Distributed.Process.Backend.SimpleLocalnet

Contents

Description

Simple backend based on the TCP transport which offers node discovery based on UDP multicast. This is a zero-configuration backend designed to get you going with Cloud Haskell quickly without imposing any structure on your application.

To simplify getting started we provide special support for master and slave nodes (see startSlave and startMaster). Use of these functions is completely optional; you can use the local backend without making use of the predefined master and slave nodes.

Minimal example
import System.Environment (getArgs)
import Control.Distributed.Process
import Control.Distributed.Process.Node (initRemoteTable)
import Control.Distributed.Process.Backend.SimpleLocalnet

master :: Backend -> [NodeId] -> Process ()
master backend slaves = do
  -- Do something interesting with the slaves
  liftIO . putStrLn $ "Slaves: " ++ show slaves
  -- Terminate the slaves when the master terminates (this is optional)
  terminateAllSlaves backend

main :: IO ()
main = do
  args <- getArgs

  case args of
    ["master", host, port] -> do
      backend <- initializeBackend host port initRemoteTable
      startMaster backend (master backend)
    ["slave", host, port] -> do
      backend <- initializeBackend host port initRemoteTable
      startSlave backend
Compiling and Running

Save to example.hs and compile using

ghc -threaded example.hs

Fire up some slave nodes (for the example, we run them on a single machine):

./example slave localhost 8080 &
./example slave localhost 8081 &
./example slave localhost 8082 &
./example slave localhost 8083 &

And start the master node:

./example master localhost 8084

which should then output:

Slaves: [nid://localhost:8083:0,nid://localhost:8082:0,nid://localhost:8081:0,nid://localhost:8080:0]

at which point the slaves should exit.

To run the example on multiple machines, you could run

./example slave 198.51.100.1 8080 &
./example slave 198.51.100.2 8080 &
./example slave 198.51.100.3 8080 &
./example slave 198.51.100.4 8080 &

on four different machines (with IP addresses 198.51.100.1..4), and run the master on a fifth node (or on any of the four machines that run the slave nodes).

It is important that every node has a unique (hostname, port number) pair, and that the hostname you use to initialize the node can be resolved by peer nodes. In other words, if you start a node and pass hostname localhost then peer nodes won't be able to reach it because localhost will resolve to a different IP address for them.

Troubleshooting

If you try the above example and the master process cannot find any slaves, then it might be that your firewall settings do not allow for UDP multicast (in particular, the default iptables on some Linux distributions might not allow it).

Synopsis

Initialization

data Backend Source

Local backend

Constructors

Backend 

Fields

newLocalNode :: IO LocalNode

Create a new local node

findPeers :: Int -> IO [NodeId]

findPeers t broadcasts a who's there? message on the local network, waits t microseconds, and then collects and returns the answers. You can use this to dynamically discover peer nodes.

redirectLogsHere :: [ProcessId] -> Process ()

Make sure that all log messages are printed by the logger on the current node

Slave nodes

startSlave :: Backend -> IO () Source

Calling slave sets up a new local node and then waits. You start processes on the slave by calling spawn from other nodes.

This function does not return. The only way to exit the slave is to CTRL-C the process or call terminateSlave from another node.

terminateSlave :: NodeId -> Process () Source

Terminate the slave at the given node ID

findSlaves :: Backend -> Process [ProcessId] Source

Find slave nodes

terminateAllSlaves :: Backend -> Process () Source

Terminate all slaves

Master nodes

startMaster :: Backend -> ([NodeId] -> Process ()) -> IO () Source

startMaster finds all slaves currently available on the local network, redirects all log messages to itself, and then calls the specified process, passing the list of slaves nodes.

Terminates when the specified process terminates. If you want to terminate the slaves when the master terminates, you should manually call terminateAllSlaves.

If you start more slave nodes after having started the master node, you can discover them with later calls to findSlaves, but be aware that you will need to call redirectLogHere to redirect their logs to the master node.

Note that you can use functionality of SimpleLocalnet directly (through Backend), instead of using 'startMaster'/'startSlave', if the master/slave distinction does not suit your application.