{-# LANGUAGE TemplateHaskell, DeriveDataTypeable, DeriveGeneric #-} {-# OPTIONS_GHC -Wall #-} import Control.Distributed.Process hiding (Message) import Control.Distributed.Process.Closure import Control.Monad import Text.Printf import GHC.Generics (Generic) import Data.Binary import Data.Typeable import DistribUtils -- <> -- <> -- <> -- < Process () master peers = do ps <- forM peers $ \nid -> do say $ printf "spawning on %s" (show nid) spawn nid $(mkStaticClosure 'pingServer) mapM_ monitor ps ports <- forM ps $ \pid -> do say $ printf "pinging %s" (show pid) (sendport,recvport) <- newChan -- <1> send pid (Ping sendport) -- <2> return recvport forM_ ports $ \port -> do -- <3> _ <- receiveChan port return () say "All pongs successfully received" terminate -- >> -- <
>