LogicGrowsOnTrees-network-1.0.0.3: an adapter for LogicGrowsOnTrees that uses multiple processes running in a network

Safe HaskellNone

LogicGrowsOnTrees.Parallel.Adapter.Network

Contents

Description

This adapter implements parallelism by allowing multiple workers to connect to a supervisor over the network. For this adapter, workers are started separately from the supervisor, so the number of workers is not set by the controller but by the number of workers that connect to supervisor.

Synopsis

Driver

driver :: forall shared_configuration supervisor_configuration m n exploration_mode. (Serialize shared_configuration, Serialize (ProgressFor exploration_mode), Serialize (WorkerFinishedProgressFor exploration_mode)) => Driver IO shared_configuration supervisor_configuration m n exploration_modeSource

This is the driver for the network adapter; it consists of a supervisor that listens for connections and multiple workers that connect to the supervisor, where the same executable is used for both the supervisor and the worker. To start the supervisor, run the executable with supervisor as the first argument and -p PORTID to specify the port id. To start a worker, run the executable with worker as the first argument, the address of the supervisor as the second, and the port id as the third.

Network

type Network = [network_secret :: NetworkSecret]Source

This constraint exists due to the quirk that on Windows one needs to initialize the network system before using it via. withSocketsDo; to ensure that this happens, all computations that use the network have the Network constrant and must be run by calling withNetwork.

withNetwork :: (Network => IO α) -> IO αSource

Initializes the network subsystem where required (e.g., on Windows).

Controller

class RequestQueueMonad m => NetworkRequestQueueMonad m whereSource

This class extends RequestQueueMonad with the ability to forcibly disconnect a worker.

Methods

disconnectWorker :: WorkerId -> m ()Source

Forcibly disconnects the given worker; calling this function with the WorkerId of a worker that is no longer connected to the system is *not* an error; in that case, nothing will happen.

data NetworkControllerMonad exploration_mode α Source

This is the monad in which the network controller will run.

abort :: RequestQueueMonad m => m ()

Abort the supervisor.

fork :: RequestQueueMonad m => m () -> m ThreadId

Fork a new thread running in this monad; all controller threads are automnatically killed when the run is finished.

getCurrentProgressAsync :: RequestQueueMonad m => (ProgressFor (ExplorationModeFor m) -> IO ()) -> m ()

Request the current progress, invoking the given callback with the result; see getCurrentProgress for the synchronous version.

getCurrentProgress :: RequestQueueMonad m => m (ProgressFor (ExplorationModeFor m))

Like getCurrentProgressAsync, but blocks until the result is ready.

getCurrentStatisticsAsync :: RequestQueueMonad m => (RunStatistics -> IO ()) -> m ()

Get the current run statistics.

getCurrentStatistics :: RequestQueueMonad m => m RunStatistics

Like getCurrentStatisticsAsync, but blocks until the result is ready.

getNumberOfWorkersAsync :: RequestQueueMonad m => (Int -> IO ()) -> m ()

Request the number of workers, invoking the given callback with the result; see getNumberOfWorkers for the synchronous version.

getNumberOfWorkers :: RequestQueueMonad m => m Int

Like getNumberOfWorkersAsync, but blocks until the result is ready.

requestProgressUpdateAsync :: RequestQueueMonad m => (ProgressFor (ExplorationModeFor m) -> IO ()) -> m ()

Request that a global progress update be performed, invoking the given callback with the result; see requestProgressUpdate for the synchronous version.

requestProgressUpdate :: RequestQueueMonad m => m (ProgressFor (ExplorationModeFor m))

Like requestProgressUpdateAsync, but blocks until the progress update has completed.

setWorkloadBufferSize :: RequestQueueMonad m => Int -> m ()

Sets the size of the workload buffer; for more information, see setWorkloadBufferSize (which links to the LogicGrowsOnTrees.Parallel.Common.Supervisor module).

Outcome types

data RunOutcome progress final_result

A type that represents the outcome of a run.

Constructors

RunOutcome 

Fields

runStatistics :: RunStatistics

statistics gathered during the run, useful if the system is not scaling with the number of workers as it should

runTerminationReason :: TerminationReason progress final_result

the reason why the run terminated

Instances

(Eq progress, Eq final_result) => Eq (RunOutcome progress final_result) 
(Show progress, Show final_result) => Show (RunOutcome progress final_result) 

data RunStatistics

Statistics gathered about the run.

Constructors

RunStatistics 

Fields

runStartTime :: !UTCTime

the start time of the run

runEndTime :: !UTCTime

the end time of the run

runWallTime :: !NominalDiffTime

the wall time of the run

runSupervisorOccupation :: !Float

the fraction of the time the supervisor spent processing events

runSupervisorMonadOccupation :: !Float

the fraction of the time the supervisor spent processing events while inside the SupervisorMonad

runNumberOfCalls :: !Int

the number of calls made to functions in LogicGrowsOnTrees.Parallel.Common.Supervisor

runAverageTimePerCall :: !Float

the average amount of time per call made to functions in LogicGrowsOnTrees.Parallel.Common.Supervisor

runWorkerCountStatistics :: !(FunctionOfTimeStatistics Int)

statistics for the number of workers waiting for a workload

runWorkerOccupation :: !Float

the fraction of the total time that workers were occupied

runWorkerWaitTimes :: !(FunctionOfTimeStatistics NominalDiffTime)

statistics for how long it took for workers to obtain a workload

runStealWaitTimes :: !IndependentMeasurementsStatistics

statistics for the time needed to steal a workload from a worker

runWaitingWorkerStatistics :: !(FunctionOfTimeStatistics Int)

statistics for the number of workers waiting for a workload

runAvailableWorkloadStatistics :: !(FunctionOfTimeStatistics Int)

statistics for the number of available workloads waiting for a worker

runInstantaneousWorkloadRequestRateStatistics :: !(FunctionOfTimeStatistics Float)

statistics for the instantaneous rate at which workloads were requested (using an exponentially decaying sum)

runInstantaneousWorkloadStealTimeStatistics :: !(FunctionOfTimeStatistics Float)

statistics for the instantaneous time needed for workloads to be stolen (using an exponentially decaying weighted average)

data TerminationReason progress final_result

A type that represents the reason why a run terminated.

Constructors

Aborted progress

the run was aborted with the given progress

Completed final_result

the run completed with the given final result

Failure progress String

the run failed with the given progress for the given reason

Instances

(Eq progress, Eq final_result) => Eq (TerminationReason progress final_result) 
(Show progress, Show final_result) => Show (TerminationReason progress final_result) 

Miscellaneous types

data NetworkCallbacks Source

Callbacks used to to notify when a worker has conneted or disconnected.

Constructors

NetworkCallbacks 

Fields

notifyConnected :: WorkerId -> IO Bool

callback used to notify that a worker is about to connect; return True to allow the connection to proceed and False to veto it

notifyDisconnected :: WorkerId -> IO ()

callback used to notify that a worker has disconnected

default_network_callbacks :: NetworkCallbacksSource

A default set of callbacks for when you don't care about being notified of connections and disconnections.

data NetworkConfiguration shared_configuration supervisor_configuration Source

Configuration information that indicates whether a process should be run in supervisor or worker mode.

Constructors

SupervisorConfiguration

This constructor indicates that the process should run in supervisor mode.

Fields

shared_configuration :: shared_configuration

configuration information shared between the supervisor and the worker

supervisor_configuration :: supervisor_configuration

configuration information specific to the supervisor

supervisor_port :: WrappedPortID
  • for the worker, the port to which to connect
  • for the supervisor, the port on which to listen
WorkerConfiguration

This constructor indicates that the process should be run in worker mode.

Fields

supervisor_host_name :: HostName

the address of the supervisor to which this worker should connect

supervisor_port :: WrappedPortID
  • for the worker, the port to which to connect
  • for the supervisor, the port on which to listen

data WorkerId Source

The ID of a worker.

Constructors

WorkerId 

Fields

workerHostName :: HostName

the address of the worker

workerPortNumber :: PortNumber

the port number of the worker

newtype WrappedPortID Source

A newtype wrapper around PortID in order to provide an instance of ArgVal.

Constructors

WrappedPortID 

Fields

unwrapPortID :: PortID
 

Generic runner functions

In this section the full functionality of this module is exposed in case one does not want the restrictions of the driver interface. If you decide to go in this direction, then you need to decide whether you want there to be a single executable for both the supervisor and worker with the process of determining in which mode it should run taken care of for you, or whether you want to do this yourself in order to give yourself more control (such as by having separate supervisor and worker executables) at the price of more work.

If you want to use a single executable with automated handling of the supervisor and worker roles, then use runExplorer. Otherwise, use runSupervisor to run the supervisor loop and on each worker use runWorker.

runSupervisorSource

Arguments

:: forall exploration_mode . (Serialize (ProgressFor exploration_mode), Serialize (WorkerFinishedProgressFor exploration_mode), Network) 
=> ExplorationMode exploration_mode

the exploration mode

-> (Handle -> IO ())

an action that writes any information needed by the worker to the given handle

-> NetworkCallbacks

callbacks used to signal when a worker has connected or disconnected; the connect callback has the ability to veto a worker from connecting

-> PortID

the port id on which to listen for connections

-> ProgressFor exploration_mode

the initial progress of the run

-> NetworkControllerMonad exploration_mode ()

the controller of the supervisor

-> IO (RunOutcomeFor exploration_mode)

the outcome of the run

This runs the supervisor, which will listen for connecting workers.

runWorkerSource

Arguments

:: (Serialize (ProgressFor exploration_mode), Serialize (WorkerFinishedProgressFor exploration_mode), Network) 
=> ExplorationMode exploration_mode

the mode in to explore the tree

-> Purity m n

the purity of the tree

-> TreeT m (ResultFor exploration_mode)

the tree

-> HostName

the address of the supervisor

-> PortID

the port id on which the supervisor is listening

-> IO () 

Runs a worker that connects to the supervisor via. the given address and port id.

runExplorerSource

Arguments

:: (Serialize shared_configuration, Serialize (ProgressFor exploration_mode), Serialize (WorkerFinishedProgressFor exploration_mode), Network) 
=> (shared_configuration -> ExplorationMode exploration_mode)

a function that constructs the exploration mode given the shared configuration

-> Purity m n

the purity of the tree

-> IO (NetworkConfiguration shared_configuration supervisor_configuration)

an action that gets the configuration information (run on both supervisor and worker processes); this also determines whether we are in supervisor or worker mode based on whether the constructor use is respectively SupervisorConfiguration or WorkerConfiguration

-> (shared_configuration -> IO ())

an action that initializes the global state of the process given the shared configuration (run on both supervisor and worker processes)

-> (shared_configuration -> TreeT m (ResultFor exploration_mode))

a function that constructs the tree from the shared configuration (called only on the worker)

-> (shared_configuration -> supervisor_configuration -> IO (ProgressFor exploration_mode))

an action that gets the starting progress given the full configuration information (run only on the supervisor)

-> (shared_configuration -> supervisor_configuration -> NetworkControllerMonad exploration_mode ())

a function that constructs the controller for the supervisor (called only on the supervisor)

-> IO (Maybe ((shared_configuration, supervisor_configuration), RunOutcomeFor exploration_mode))

if this process is the supervisor, then the outcome of the run as well as the configuration information wrapped in Just; otherwise Nothing

Explores the given tree using multiple processes to achieve parallelism.

This function grants access to all of the functionality of this adapter, rather than having to go through the more restricted driver interface. The signature of this function is very complicated because it is meant to be used in both the supervisor and worker. The configuration information is used to determine whether the program is being run in supervisor mode or in worker mode; in the former case, the configuration is further split into configuration information that is shared between the supervisor and the worker and configuration information that is specific to the supervisor.

Utility functions

showPortID :: PortID -> StringSource

Constructs a string representation of a port id. (This function is needed if using an older version of the Network package that doesn't have a Show instance for PortID.)

getConfigurationSource

Arguments

:: Term shared_configuration

configuration that is shared between the supervisor and the worker

-> Term supervisor_configuration

configuration that is specific to the supervisor

-> TermInfo

program information (you should at least set termDoc with the program description)

-> IO (NetworkConfiguration shared_configuration supervisor_configuration)

the configuration obtained from the command line

Processes the command line and returns the network configuration; it uses the first argument to determine whether the configuration should be for a supervisor or for a worker.