Skip to content

Instantly share code, notes, and snippets.

@mboes
Created May 29, 2015 21:54
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save mboes/159391c8ae1c1939464e to your computer and use it in GitHub Desktop.
Save mboes/159391c8ae1c1939464e to your computer and use it in GitHub Desktop.
distributed collatz
{-# LANGUAGE TemplateHaskell #-}
module Main where
import Control.Distributed.Process
import Control.Distributed.Process.Closure
import Control.Distributed.Process.Node
import Control.Distributed.Process.Backend.SimpleLocalnet
import System.Environment (getArgs, getProgName)
collatz :: Int -> Int
collatz 1 = 1
collatz x
| even x = x `div` 2
| otherwise = 3 * x + 1
remotableDecl [ [d|
distributedCollatz :: ([NodeId], Int) -> Process ()
distributedCollatz (slaves, x) = do
let x' = collatz x
say $ show x ++ " goes to " ++ show x'
_ <- spawn (head slaves) $ $(mkClosure 'distributedCollatz) (slaves, collatz x)
return ()
|]]
remoteTable = __remoteTableDecl initRemoteTable
master :: Backend -> [NodeId] -> Process ()
master backend slaves = do
liftIO . putStrLn $ "Slaves: " ++ show slaves
distributedCollatz (slaves, 27)
liftIO $ getLine
terminateAllSlaves backend
main :: IO ()
main = do
prog <- getProgName
args <- getArgs
case args of
["master", host, port] -> do
backend <- initializeBackend host port remoteTable
startMaster backend (master backend)
["slave", host, port] -> do
backend <- initializeBackend host port remoteTable
startSlave backend
_ ->
putStrLn $ "usage: " ++ prog ++ " (master | slave) host port"
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment