Safe Haskell | None |
---|
LogicGrowsOnTrees.Parallel.Adapter.Processes
Description
This adapter implements parallelism by spawning multiple processes. The number of processes can be changed during the run and even be set to zero.
- driver :: (Serialize shared_configuration, Serialize (ProgressFor exploration_mode), Serialize (WorkerFinishedProgressFor exploration_mode)) => Driver IO shared_configuration supervisor_configuration m n exploration_mode
- data ProcessesControllerMonad exploration_mode α
- abort :: RequestQueueMonad m => m ()
- changeNumberOfWorkersAsync :: WorkgroupRequestQueueMonad m => (Word -> Word) -> (Word -> IO ()) -> m ()
- changeNumberOfWorkers :: WorkgroupRequestQueueMonad m => (Word -> Word) -> m Word
- fork :: RequestQueueMonad m => m () -> m ThreadId
- getCurrentProgressAsync :: RequestQueueMonad m => (ProgressFor (ExplorationModeFor m) -> IO ()) -> m ()
- getCurrentProgress :: RequestQueueMonad m => m (ProgressFor (ExplorationModeFor m))
- getNumberOfWorkersAsync :: RequestQueueMonad m => (Int -> IO ()) -> m ()
- getNumberOfWorkers :: RequestQueueMonad m => m Int
- requestProgressUpdateAsync :: RequestQueueMonad m => (ProgressFor (ExplorationModeFor m) -> IO ()) -> m ()
- requestProgressUpdate :: RequestQueueMonad m => m (ProgressFor (ExplorationModeFor m))
- setNumberOfWorkersAsync :: WorkgroupRequestQueueMonad m => Word -> IO () -> m ()
- setNumberOfWorkers :: WorkgroupRequestQueueMonad m => Word -> m ()
- setWorkloadBufferSize :: RequestQueueMonad m => Int -> m ()
- data RunOutcome progress final_result
- data RunStatistics = RunStatistics {
- runStartTime :: !UTCTime
- runEndTime :: !UTCTime
- runWallTime :: !NominalDiffTime
- runSupervisorOccupation :: !Float
- runSupervisorMonadOccupation :: !Float
- runNumberOfCalls :: !Int
- runAverageTimePerCall :: !Float
- runWorkerOccupation :: !Float
- runWorkerWaitTimes :: !(FunctionOfTimeStatistics NominalDiffTime)
- runStealWaitTimes :: !IndependentMeasurementsStatistics
- runWaitingWorkerStatistics :: !(FunctionOfTimeStatistics Int)
- runAvailableWorkloadStatistics :: !(FunctionOfTimeStatistics Int)
- runInstantaneousWorkloadRequestRateStatistics :: !(FunctionOfTimeStatistics Float)
- runInstantaneousWorkloadStealTimeStatistics :: !(FunctionOfTimeStatistics Float)
- data TerminationReason progress final_result
- runSupervisor :: (Serialize (ProgressFor exploration_mode), Serialize (WorkerFinishedProgressFor exploration_mode)) => ExplorationMode exploration_mode -> String -> [String] -> (Handle -> IO ()) -> ProgressFor exploration_mode -> ProcessesControllerMonad exploration_mode () -> IO (RunOutcomeFor exploration_mode)
- runWorker :: ExplorationMode exploration_mode -> Purity m n -> TreeT m (ResultFor exploration_mode) -> IO MessageForWorker -> (MessageForSupervisorFor exploration_mode -> IO ()) -> IO ()
- runWorkerUsingHandles :: (Serialize (ProgressFor exploration_mode), Serialize (WorkerFinishedProgressFor exploration_mode)) => ExplorationMode exploration_mode -> Purity m n -> TreeT m (ResultFor exploration_mode) -> Handle -> Handle -> IO ()
- runExplorer :: (Serialize shared_configuration, Serialize (ProgressFor exploration_mode), Serialize (WorkerFinishedProgressFor exploration_mode)) => (shared_configuration -> ExplorationMode exploration_mode) -> Purity m n -> IO (shared_configuration, supervisor_configuration) -> (shared_configuration -> IO ()) -> (shared_configuration -> TreeT m (ResultFor exploration_mode)) -> (shared_configuration -> supervisor_configuration -> IO (ProgressFor exploration_mode)) -> (shared_configuration -> supervisor_configuration -> ProcessesControllerMonad exploration_mode ()) -> IO (Maybe ((shared_configuration, supervisor_configuration), RunOutcomeFor exploration_mode))
- getProgFilepath :: IO String
Driver
driver :: (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 threads adapter; the number of workers is specified via. the (required) command-line option -n.
Note that there are not seperate drivers for the supervisor process and the worker process; instead, the same executable is used for both the supervisor and the worker, with a sentinel argument (or arguments) determining which role it should run as.
Controller
data ProcessesControllerMonad exploration_mode α Source
The monad in which the processes controller will run.
Instances
Monad (ProcessesControllerMonad exploration_mode) | |
Functor (ProcessesControllerMonad exploration_mode) | |
Applicative (ProcessesControllerMonad exploration_mode) | |
MonadIO (ProcessesControllerMonad exploration_mode) | |
WorkgroupRequestQueueMonad (ProcessesControllerMonad exploration_mode) | |
RequestQueueMonad (ProcessesControllerMonad exploration_mode) | |
HasExplorationMode (ProcessesControllerMonad exploration_mode) | |
MonadCatchIO (ProcessesControllerMonad exploration_mode) |
abort :: RequestQueueMonad m => m ()
Abort the supervisor.
changeNumberOfWorkersAsync :: WorkgroupRequestQueueMonad m => (Word -> Word) -> (Word -> IO ()) -> m ()
Change the number of workers; the first argument is a map that computes the new number of workers given the old number of workers, and the second argument is a callback that will be invoked with the new number of workers.
See changeNumberOfWorkers
for the synchronous version of this request.
If you just want to set the number of workers to some fixed value, then
see setNumberOfWorkers
/ setNumberOfWorkersAsync
.
changeNumberOfWorkers :: WorkgroupRequestQueueMonad m => (Word -> Word) -> m Word
Like changeNumberOfWorkersAsync
, but it blocks until the number of workers
has been changed and returns the new number of workers.
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.
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.
setNumberOfWorkersAsync :: WorkgroupRequestQueueMonad m => Word -> IO () -> m ()
Request that the number of workers be set to the given amount, invoking the given callback when this has been done.
setNumberOfWorkers :: WorkgroupRequestQueueMonad m => Word -> m ()
Like setNumberOfWorkersAsync
, but blocks until the number of workers has been set to the desired value.
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.
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
|
Instances
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) |
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
runWorkerUsingHandles
, passing stdin
and stdout
as the process handles.
Arguments
:: (Serialize (ProgressFor exploration_mode), Serialize (WorkerFinishedProgressFor exploration_mode)) | |
=> ExplorationMode exploration_mode | the exploration mode |
-> String | the path to the worker executable |
-> [String] | the arguments to pass to the worker executable |
-> (Handle -> IO ()) | an action that writes any information needed by the worker to the given handle |
-> ProgressFor exploration_mode | the initial progress of the run |
-> ProcessesControllerMonad exploration_mode () | the controller of the supervisor, which must at least set the number of workers to be positive for anything to take place |
-> IO (RunOutcomeFor exploration_mode) | the result of the run |
This runs the supervisor, which will spawn and kill worker processes as needed so that the total number is equal to the number set by the controller.
Arguments
:: 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 |
-> IO MessageForWorker | the action used to fetch the next message |
-> (MessageForSupervisorFor exploration_mode -> IO ()) | the action to send a message to the supervisor; note that this might occur in a different thread from the worker loop |
-> IO () |
Runs a loop that continually fetches and reacts to messages from the supervisor until the worker quits.
Arguments
:: (Serialize (ProgressFor exploration_mode), Serialize (WorkerFinishedProgressFor exploration_mode)) | |
=> 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 |
-> Handle | handle from which messages from the supervisor are read |
-> Handle | handle to which messages to the supervisor are written |
-> IO () |
The same as runWorker
, but it lets you provide handles through which the
messages will be sent and received. (Note that the reading and writing
handles might be the same.)
Arguments
:: (Serialize shared_configuration, Serialize (ProgressFor exploration_mode), Serialize (WorkerFinishedProgressFor exploration_mode)) | |
=> (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 (shared_configuration, supervisor_configuration) | an action that gets the shared and supervisor-specific configuration information (run only on the supervisor) |
-> (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 -> ProcessesControllerMonad exploration_mode ()) | a function that constructs the controller for the supervisor, which must at least set the number of workers to be non-zero (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 |
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; it figures out which role it is supposed to play based on whether the list of command line arguments matches a sentinel.
The configuration information is divided into two parts: information shared between the supervisor and the workers, and information that is specific to the supervisor and not sent to the workers. (Note that only the former needs to be serializable.) An action must be supplied that obtains this configuration information, and most of the arguments are functions that are given all or part of this information.
Utility functions
getProgFilepath :: IO StringSource
Gets the full path to this executable.