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

Safe HaskellNone

LogicGrowsOnTrees.Parallel.Common.Workgroup

Contents

Description

This module provides most of the common functionality needed to implement a adapter where the number of workers can be adjusted during the run.

Synopsis

Type-classes

class RequestQueueMonad m => WorkgroupRequestQueueMonad m whereSource

A WorkgroupRequestQueueMonad is a RequestQueueMonad but with the additional ability to change the number of workers in the system.

Methods

changeNumberOfWorkersAsync :: (Word -> Word) -> (Word -> IO ()) -> m ()Source

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.

Types

type InnerMonad inner_state = StateT inner_state IOSource

This is the monad in which the adapter specific code is run.

data MessageForSupervisorReceivers exploration_mode worker_id Source

This data structure contains callbacks to be invoked when a message has been received, depending on the kind of message.

Constructors

MessageForSupervisorReceivers 

Fields

receiveProgressUpdateFromWorker :: worker_id -> ProgressUpdate (ProgressFor exploration_mode) -> IO ()

to be called when a progress update has been received from a worker

receiveStolenWorkloadFromWorker :: worker_id -> Maybe (StolenWorkload (ProgressFor exploration_mode)) -> IO ()

to be called when a (possibly) stolen workload has been received from a worker

receiveFailureFromWorker :: worker_id -> String -> IO ()

to be called when a failure (with the given message) has been received from a worker

receiveFinishedFromWorker :: worker_id -> WorkerFinishedProgressFor exploration_mode -> IO ()

to be called when a worker has finished with the given final progress

receiveQuitFromWorker :: worker_id -> IO ()

to be called when a worker has quit the system and is no longer available

type WorkerId = IntSource

The type of worker ids used by this module (an alias for Int).

data WorkgroupCallbacks inner_state Source

A set of callbacks invoked by the supervisor code in this module.

Constructors

WorkgroupCallbacks 

Fields

createWorker :: WorkerId -> InnerMonad inner_state ()

create a worker with the given id

destroyWorker :: WorkerId -> Bool -> InnerMonad inner_state ()

destroy the worker with the given id; ideally this should be implemented by signaling the worker to quit and then waiting for an acknowledgement

killAllWorkers :: [WorkerId] -> InnerMonad inner_state ()

destroy all of the workers in the given list in a manner that ensures they all terminate promptly; this will be called at the end of the run (successful or not)

sendProgressUpdateRequestTo :: WorkerId -> InnerMonad inner_state ()

send a progress update request to the given worker

sendWorkloadStealRequestTo :: WorkerId -> InnerMonad inner_state ()

send a workload steal request to the given worker

sendWorkloadTo :: WorkerId -> Workload -> InnerMonad inner_state ()

send a workload to the given worker

newtype WorkgroupControllerMonad inner_state exploration_mode α Source

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

Constructors

C 

Fields

unwrapC :: RequestQueueReader exploration_mode WorkerId (WorkgroupStateMonad inner_state) α
 

Instances

Monad (WorkgroupControllerMonad inner_state exploration_mode) 
Functor (WorkgroupControllerMonad inner_state exploration_mode) 
Applicative (WorkgroupControllerMonad inner_state exploration_mode) 
MonadCatchIO (WorkgroupControllerMonad inner_state exploration_mode) 
MonadIO (WorkgroupControllerMonad inner_state exploration_mode) 
HasExplorationMode (WorkgroupControllerMonad inner_state exploration_mode) 
RequestQueueMonad (WorkgroupControllerMonad inner_state exploration_mode) 
WorkgroupRequestQueueMonad (WorkgroupControllerMonad inner_state exploration_mode) 

Functions

Worker count adjustment

changeNumberOfWorkers :: WorkgroupRequestQueueMonad m => (Word -> Word) -> m WordSource

Like changeNumberOfWorkersAsync, but it blocks until the number of workers has been changed and returns the new number of workers.

setNumberOfWorkersAsync :: WorkgroupRequestQueueMonad m => Word -> IO () -> m ()Source

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 ()Source

Like setNumberOfWorkersAsync, but blocks until the number of workers has been set to the desired value.

Runner

runWorkgroupSource

Arguments

:: ExplorationMode exploration_mode

the mode in which we are exploring the tree

-> inner_state

the initial adapter specific state of the inner monad

-> (MessageForSupervisorReceivers exploration_mode WorkerId -> WorkgroupCallbacks inner_state)

a function that constructs a set of callbacks to be used by the supervisor loop in this function to do things like creating and destroying workers; it is given a set of callbacks that allows the adapter specific code to signal conditions to the supervisor

-> ProgressFor exploration_mode

the initial progress of the exploration

-> WorkgroupControllerMonad inner_state exploration_mode ()

the controller, which is at the very least responsible for deciding how many workers should be initially created

-> IO (RunOutcomeFor exploration_mode) 

Explores a tree using a workgroup; this function is only intended to be used by adapters where the number of workers can be changed on demand.