LogicGrowsOnTrees-1.0.0.0.1: a parallel implementation of logic programming using distributed tree exploration

Safe HaskellNone

LogicGrowsOnTrees.Parallel.Common.Supervisor

Contents

Description

The Supervisor module contains logic that is common to all of the adapters for the parallization infrastructure. The way to use it is to package the logic for communicating with your workers into a SupervisorProgram that runs in the SupervisorMonad with your state just below the SupervisorMonad in the monad stack.

A great deal of the logic in this module deals with gathering statistics whose purpose is to provide data that can be used to figure out what is going wrong if the runtime is not scaling inversely with the number of workers.

Synopsis

Types

Statistics

data FunctionOfTimeStatistics α Source

Statistics for a value obtained by integrating a value that is a function of time --- i.e., a quantity that holds a single value at any given point in time.

Constructors

FunctionOfTimeStatistics 

Fields

timeCount :: !Word

the number of points at which the function changed

timeAverage :: !Double

the average value of the function over the time period

timeStdDev :: !Double

the standard deviation of the function over the time period

timeMin :: !α

the minimum value of the function over the time period

timeMax :: !α

the maximum value of the function over the time period

data IndependentMeasurementsStatistics Source

Statistics for a value obtained by collecting a number of independent measurements.

Constructors

IndependentMeasurementsStatistics 

Fields

statCount :: !Int

the number of measurements

statAverage :: !Double

the average value

statStdDev :: !Double

the standard deviation

statMin :: !Double

the minimum measurement value

statMax :: !Double

the maximum measurement value

data RunStatistics Source

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

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)

Constraints

type SupervisorMonadConstraint m = (Functor m, MonadIO m)Source

This is the constraint placed on the monad in which the supervisor is running.

type SupervisorWorkerIdConstraint worker_id = (Eq worker_id, Ord worker_id, Show worker_id, Typeable worker_id)Source

This is the constraint placed on the types that can be used as worker ids.

Supervisor types

data SupervisorCallbacks exploration_mode worker_id m Source

Supervisor callbacks provide the means by which the supervisor logic communicates to the adapter, usually in order to tell it what it wants to say to various workers.

Constructors

SupervisorCallbacks 

Fields

broadcastProgressUpdateToWorkers :: [worker_id] -> m ()

send a progress update request to the given workers

broadcastWorkloadStealToWorkers :: [worker_id] -> m ()

send a workload steal request to the given workers

receiveCurrentProgress :: ProgressFor exploration_mode -> m ()

receive the result of the global progress update that was requested by the controller

sendWorkloadToWorker :: Workload -> worker_id -> m ()

send the given workload to the given worker

data SupervisorMonad exploration_mode worker_id m α Source

This is the monad in which the supervisor logic is run; it keeps track of the state of the system including the current workers and their workloads, the current progress of the system, which workers we are waiting for a progress update or stolen workload from, etc.

Instances

MonadReader e m => MonadReader e (SupervisorMonad exploration_mode worker_id m) 
MonadState s m => MonadState s (SupervisorMonad exploration_mode worker_id m) 
MonadTrans (SupervisorMonad exploration_mode worker_id) 
Monad m => Monad (SupervisorMonad exploration_mode worker_id m) 
Functor m => Functor (SupervisorMonad exploration_mode worker_id m) 
(Monad m, Functor m) => Applicative (SupervisorMonad exploration_mode worker_id m) 
MonadIO m => MonadIO (SupervisorMonad exploration_mode worker_id m) 

data SupervisorOutcome final_result progress worker_id Source

The outcome of running the supervisor.

Constructors

SupervisorOutcome 

Fields

supervisorTerminationReason :: SupervisorTerminationReason final_result progress worker_id

the reason the supervisor terminated

supervisorRunStatistics :: RunStatistics

the statistics for the run

supervisorRemainingWorkers :: [worker_id]

the workers that were present when it finished

Instances

(Eq final_result, Eq progress, Eq worker_id) => Eq (SupervisorOutcome final_result progress worker_id) 
(Show final_result, Show progress, Show worker_id) => Show (SupervisorOutcome final_result progress worker_id) 

type SupervisorOutcomeFor exploration_mode worker_id = SupervisorOutcome (FinalResultFor exploration_mode) (ProgressFor exploration_mode) worker_idSource

A convenient type alias for the SupervisorOutcome associated with a given exploration mode.

data SupervisorProgram exploration_mode worker_id m Source

A SupervisorProgram is a specification of an event loop to be run inside the SupervisorMonad; it exists in order to help the supervisor get an estimate for how much time it is spending doing work as opposed to waiting for a message from a worker so that it can generate accurate statistics about how much of the time it was occupied at the end of the run.

Constructors

forall α . BlockingProgram (SupervisorMonad exploration_mode worker_id m ()) (m α) (α -> SupervisorMonad exploration_mode worker_id m ())

A BlockingProgram has an event loop that executes an action that pauses the thread until an event occurs and then reacts to that event. The first argument is the supervisor action that initializes the system, the second argument is an action that blocks until an event has occurred, and the third argument is the supervisor action to run in response to the event.

forall α . PollingProgram (SupervisorMonad exploration_mode worker_id m ()) (m (Maybe α)) (α -> SupervisorMonad exploration_mode worker_id m ())

A PollingProgram has an event loop that executes an action that checks whether an event has occurred and if so then reacts to that event. The first argument is the supervisor action that initializes the system, the second argument is an action that checks whether an event has occurred, and the third argument is the supervisor action to run in response to an event.

UnrestrictedProgram (forall α. SupervisorMonad exploration_mode worker_id m α)

An UnrestrictedProgram is an event loop that you implement manually; note that it must run forever until the logic in the SupervisorMonad decides to exit --- although you can always force it to abort by calling abortSupervisor. This mode exists for testing rather than to be used by an adapter, but if you do use it then you take on responsibility for calling beginSupervisorOccupied and endSupervisorOccupied when respectively the supervisor has begun and ended processing events so that the supervisor occupation statistics are correct.

data SupervisorTerminationReason final_result progress worker_id Source

The reason why the supervisor terminated.

Constructors

SupervisorAborted progress

the supervisor aborted before finishing; included is the current progress at the time it aborted

SupervisorCompleted final_result

the supervisor completed exploring the tree; included is the final result

SupervisorFailure progress worker_id String

the supervisor failed to explore the tree; included is the worker where the failure occured as well as the message and the current progress at the time of failure

Instances

(Eq final_result, Eq progress, Eq worker_id) => Eq (SupervisorTerminationReason final_result progress worker_id) 
(Show final_result, Show progress, Show worker_id) => Show (SupervisorTerminationReason final_result progress worker_id) 

type SupervisorTerminationReasonFor exploration_mode = SupervisorTerminationReason (FinalResultFor exploration_mode) (ProgressFor exploration_mode)Source

A convenient type alias for the SupervisorTerminationReason associated with a given exploration mode.

Functions

Worker interaction

addWorker :: (SupervisorMonadConstraint m, SupervisorWorkerIdConstraint worker_id) => worker_id -> SupervisorMonad exploration_mode worker_id m ()Source

Informs the supervisor that a worker has been added to the system; the supervisor will attempt to obtain a workload for it, stealing one if necessary.

performGlobalProgressUpdate :: (SupervisorMonadConstraint m, SupervisorWorkerIdConstraint worker_id) => SupervisorMonad exploration_mode worker_id m ()Source

Request that a global progress update be performed; the supervisor will send progress update requests to all workers, and when it has received a response from everyone it will call the receiveCurrentProgress callback in the SupervisorCallbacks.

receiveProgressUpdate :: (SupervisorMonadConstraint m, SupervisorWorkerIdConstraint worker_id) => worker_id -> ProgressUpdateFor exploration_mode -> SupervisorMonad exploration_mode worker_id m ()Source

Informs the supervisor that a progress update has been received by a worker.

receiveStolenWorkload :: (SupervisorMonadConstraint m, SupervisorWorkerIdConstraint worker_id) => worker_id -> Maybe (StolenWorkloadFor exploration_mode) -> SupervisorMonad exploration_mode worker_id m ()Source

Informs the supervisor that a worker has responded to a workload steal request; a Nothing indicates that the worker did not have a workload that could be stolen (which occurs if it hadn't taken any branches at the time the request was received).

receiveWorkerFailure :: SupervisorFullConstraint worker_id m => worker_id -> String -> SupervisorMonad exploration_mode worker_id m αSource

Informs the supervisor that a worker has failed; the system will be terminated and the given message returned as the failure message.

receiveWorkerFinished :: (SupervisorMonadConstraint m, SupervisorWorkerIdConstraint worker_id) => worker_id -> WorkerFinishedProgressFor exploration_mode -> SupervisorMonad exploration_mode worker_id m ()Source

Informs the supervisor that a worker has finished its current workload and returned the given final progress.

receiveWorkerFinishedAndRemoved :: (SupervisorMonadConstraint m, SupervisorWorkerIdConstraint worker_id) => worker_id -> WorkerFinishedProgressFor exploration_mode -> SupervisorMonad exploration_mode worker_id m ()Source

Informs the supervisor that a worker has finished its current workload and returned the given final progress; the worker will be removed after its final progress has been processed.

receiveWorkerFinishedWithRemovalFlag :: (SupervisorMonadConstraint m, SupervisorWorkerIdConstraint worker_id) => Bool -> worker_id -> WorkerFinishedProgressFor exploration_mode -> SupervisorMonad exploration_mode worker_id m ()Source

Informs the supervisor that a worker has finished its current workload and returned the given final progress; if the first argument is True then the worker will be removed.

removeWorker :: (SupervisorMonadConstraint m, SupervisorWorkerIdConstraint worker_id) => worker_id -> SupervisorMonad exploration_mode worker_id m ()Source

Informs the supervisor that a worker (which might have been active and possibly even waited on for a progress update and/or stolen workload) has been removed; the worker will be removed from the set of workers with pending requests and its workload will be returned to the pool of available workloads.

removeWorkerIfPresent :: (SupervisorMonadConstraint m, SupervisorWorkerIdConstraint worker_id) => worker_id -> SupervisorMonad exploration_mode worker_id m ()Source

Like removeWorker, but only acts if the worker is present.

Supervisor interaction

abortSupervisor :: SupervisorFullConstraint worker_id m => SupervisorMonad exploration_mode worker_id m αSource

Aborts the supervisor.

beginSupervisorOccupied :: SupervisorMonadConstraint m => SupervisorMonad exploration_mode worker_id m ()Source

Signals that the supervisor has begun processing an event.

disableSupervisorDebugMode :: SupervisorMonadConstraint m => SupervisorMonad exploration_mode worker_id m ()Source

Turns off debug mode; for more details see setSupervisorDebugMode.

enableSupervisorDebugMode :: SupervisorMonadConstraint m => SupervisorMonad exploration_mode worker_id m ()Source

Turns on debug mode; for more details see setSupervisorDebugMode.

endSupervisorOccupied :: SupervisorMonadConstraint m => SupervisorMonad exploration_mode worker_id m ()Source

Signals that the supervisor has finished processing an event.

setSupervisorDebugMode :: SupervisorMonadConstraint m => Bool -> SupervisorMonad exploration_mode worker_id m ()Source

Sets whether the supervisor is in debug mode; when it is in this mode it performs continuous self-consistency checks. This mode is intended for assisting in debugging new adapters.

setWorkloadBufferSize :: SupervisorMonadConstraint m => Int -> SupervisorMonad exploration_mode worker_id m ()Source

Sets the workload buffer size, which is the minimum number of workloads that the supervisor will attempt to have available at all times so that requests for new workloads from workers can be responded to immediately.

Normally the default value of 4 will be fine, but if you run into a problem where the amount of time needed to steal a workload is greater than the average time between requests for new workloads, then setting this to be proportional to the time needed to steal a workload divided by the time between workload requests may help.

Inquiries

getCurrentProgress :: SupervisorMonadConstraint m => SupervisorMonad exploration_mode worker_id m (ProgressFor exploration_mode)Source

Gets the current progress of the system.

getCurrentStatistics :: SupervisorFullConstraint worker_id m => SupervisorMonad exploration_mode worker_id m RunStatisticsSource

Gets the current statistics of the system. (Unlike the other "get" operations, there is a small but non-zero cost to do this as the statistics exist in an intermediate state that needs to be finalized.)

getNumberOfWorkers :: SupervisorMonadConstraint m => SupervisorMonad exploration_mode worker_id m IntSource

Gets the number of workers that are currently present in the system.

tryGetWaitingWorker :: (SupervisorMonadConstraint m, SupervisorWorkerIdConstraint worker_id) => SupervisorMonad exploration_mode worker_id m (Maybe worker_id)Source

If there exists any workers waiting for a workload, it returns the id of one of them wrapped in Just; it not, it returns Nothing. (This is useful, for example, if you want to reduce the number of workers as it is best to start by removing ones that are currently idle.)

Launching the supervisor

runSupervisor :: (SupervisorMonadConstraint m, SupervisorWorkerIdConstraint worker_id) => ExplorationMode exploration_mode -> SupervisorCallbacks exploration_mode worker_id m -> SupervisorProgram exploration_mode worker_id m -> m (SupervisorOutcomeFor exploration_mode worker_id)Source

Runs the supervisor in the given exploration mode with the given callbacks and program.

runSupervisorStartingFrom :: (SupervisorMonadConstraint m, SupervisorWorkerIdConstraint worker_id) => ExplorationMode exploration_mode -> ProgressFor exploration_mode -> SupervisorCallbacks exploration_mode worker_id m -> SupervisorProgram exploration_mode worker_id m -> m (SupervisorOutcomeFor exploration_mode worker_id)Source

Like runSupervisor but starting from the given progress.

Testing the supervisor

runUnrestrictedSupervisor :: (SupervisorMonadConstraint m, SupervisorWorkerIdConstraint worker_id) => ExplorationMode exploration_mode -> SupervisorCallbacks exploration_mode worker_id m -> (forall α. SupervisorMonad exploration_mode worker_id m α) -> m (SupervisorOutcomeFor exploration_mode worker_id)Source

Runs the supervisor with a raw action in the SupervisorMonad.

NOTE: You should not normally use this function, as it exists primarily for testing purposes; see SupervisorProgram for details.

runUnrestrictedSupervisorStartingFrom :: (SupervisorMonadConstraint m, SupervisorWorkerIdConstraint worker_id) => ExplorationMode exploration_mode -> ProgressFor exploration_mode -> SupervisorCallbacks exploration_mode worker_id m -> (forall α. SupervisorMonad exploration_mode worker_id m α) -> m (SupervisorOutcomeFor exploration_mode worker_id)Source

Like runUnrestrictedSupervisor but starting from the given progress.