{-# LANGUAGE TemplateHaskell, DeriveDataTypeable, DeriveGeneric #-} {-# OPTIONS_GHC -Wall #-} import Control.Distributed.Process import Control.Distributed.Process.Closure import Text.Printf import GHC.Generics (Generic) import Data.Binary import Data.Typeable import DistribUtils -- <> -- <> -- <> master :: Process () master = do node <- getSelfNode say $ printf "spawning on %s" (show node) pid <- spawn node $(mkStaticClosure 'pingServer) mypid <- getSelfPid say $ printf "sending ping to %s" (show pid) -- < receiveWait [ match $ \(Pong _) -> do say "pong." terminate , match $ \(ProcessMonitorNotification _ref deadpid reason) -> do say (printf "process %s died: %s" (show deadpid) (show reason)) terminate ] -- >> -- <
master) Main.__remoteTable -- >>