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

Safe HaskellNone

LogicGrowsOnTrees.Parallel.Adapter.Threads

Contents

Description

This adapter implements parallelism by spawning multiple worker threads, the number of which can be changed arbitrarily during the run.

NOTE: For the use of threads to results in parallelization, you need to make sure that the number of capabilities is at least as large as the largest number of worker threads you will be spawning. If you are using the driver, then this will be taken care of for you. If not, then you will need to either call setNumCapabilities (but only to increase the number of threads in GHC 7.4, and not too often as it may crash) or use the command-line argument +RTS -N#, where # is the number of threads you want to run in parallel. The driver takes care of this automatically by calling setNumCapabilities a single time to set the number of capabilities equal to the number of request threads (provided via. a command-line argument).

Synopsis

Driver

driver :: 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; setNumCapabilities is called exactly once to make sure that there is an equal number of capabilities.

Controller

data ThreadsControllerMonad exploration_mode α Source

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

abort :: RequestQueueMonad m => m ()Source

Abort the supervisor.

changeNumberOfWorkersAsync :: WorkgroupRequestQueueMonad m => (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.

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.

changeNumberOfWorkersToMatchCapabilities :: ThreadsControllerMonad exploration_mode ()Source

Changes the number of a parallel workers to equal the number of capabilities as reported by getNumCapabilities.

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

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

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

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

Like getCurrentProgressAsync, but blocks until the result is ready.

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

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

getNumberOfWorkers :: RequestQueueMonad m => m IntSource

Like getNumberOfWorkersAsync, but blocks until the result is ready.

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

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

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

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.

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

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 Source

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

data TerminationReason progress final_result Source

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) 

Exploration functions

The functions in this section are provided as a way to use the Threads adapter directly rather than using the framework provided in LogicGrowsOnTrees.Parallel.Main. They are all specialized versions of runExplorer, which appears in the following section. The specialized versions are provided for convenience --- specifically, to minimize the knowledge needed of the implementation and how the types specialize for the various exploration modes.

There are 3 × 2 × 4 = 24 functions in this section; the factor of 3 comes from the fact that there are three cases of monad in which the exploration is run: pure, IO, and impure (where IO is a special case of impure provided for convenience); the factor of 2 comes from the fact that one can either start with no progress or start with a given progress; and the factor of 4 comes from the fact that there are four exploration modes: summing over all results, returning the first result, summing over all results until a criteria is met with intermediate results only being sent to the supervisor upon request, and the previous mode but with all intermediate results being sent immediately to the supervisor.

Sum over all results

The functions in this section are for when you want to sum over all the results in (the leaves of) the tree.

exploreTreeSource

Arguments

:: Monoid result 
=> ThreadsControllerMonad (AllMode result) ()

the controller loop, which at the very least must start by increasing the number of workers from 0 to the desired number

-> Tree result

the (pure) tree

-> IO (RunOutcome (Progress result) result)

the outcome of the run

Explore the pure tree and sum over all results.

exploreTreeStartingFromSource

Arguments

:: Monoid result 
=> Progress result

the starting progress

-> ThreadsControllerMonad (AllMode result) ()

the controller loop, which at the very least must start by increasing the number of workers from 0 to the desired number

-> Tree result

the (pure) tree

-> IO (RunOutcome (Progress result) result)

the outcome of the run

Like exploreTree but with a starting progress.

exploreTreeIOSource

Arguments

:: Monoid result 
=> ThreadsControllerMonad (AllMode result) ()

the controller loop, which at the very least must start by increasing the number of workers from 0 to the desired number

-> TreeIO result

the tree (which runs in the IO monad)

-> IO (RunOutcome (Progress result) result)

the outcome of the run

Like exploreTree but with the tree running in IO.

exploreTreeIOStartingFromSource

Arguments

:: Monoid result 
=> Progress result

the starting progress

-> ThreadsControllerMonad (AllMode result) ()

the controller loop, which at the very least must start by increasing the number of workers from 0 to the desired number

-> TreeIO result

the tree (which runs in the IO monad)

-> IO (RunOutcome (Progress result) result)

the outcome of the run

Like exploreTreeIO but with a starting progress.

exploreTreeTSource

Arguments

:: (Monoid result, MonadIO m) 
=> (forall α. m α -> IO α)

a function that runs the tree's monad in IO

-> ThreadsControllerMonad (AllMode result) ()

the controller loop, which at the very least must start by increasing the number of workers from 0 to the desired number

-> TreeT m result

the (impure) tree

-> IO (RunOutcome (Progress result) result)

the outcome of the run

Like exploreTree but with a generic impure tree.

exploreTreeTStartingFromSource

Arguments

:: (Monoid result, MonadIO m) 
=> (forall α. m α -> IO α)

a function that runs the tree's monad in IO

-> Progress result

the starting progress

-> ThreadsControllerMonad (AllMode result) ()

the controller loop, which at the very least must start by increasing the number of workers from 0 to the desired number

-> TreeT m result

the (impure) tree

-> IO (RunOutcome (Progress result) result) 

Like exploreTreeT, but with a starting progress.

Stop at first result

For more details, follow this link: LogicGrowsOnTrees.Parallel.Main

exploreTreeUntilFirstSource

Arguments

:: ThreadsControllerMonad (FirstMode result) ()

the controller loop, which at the very least must start by increasing the number of workers from 0 to the desired number

-> Tree result

the (pure) tree

-> IO (RunOutcome Checkpoint (Maybe (Progress result)))

the outcome of the run

Explore the pure tree until a result has been found.

exploreTreeUntilFirstStartingFromSource

Arguments

:: Checkpoint

the starting progress

-> ThreadsControllerMonad (FirstMode result) ()

the controller loop, which at the very least must start by increasing the number of workers from 0 to the desired number

-> Tree result

the (pure) tree

-> IO (RunOutcome Checkpoint (Maybe (Progress result)))

the outcome of the run

Like exploreTreeUntilFirst but with a starting progress.

exploreTreeIOUntilFirstSource

Arguments

:: ThreadsControllerMonad (FirstMode result) ()

the controller loop, which at the very least must start by increasing the number of workers from 0 to the desired number

-> TreeIO result

the tree (which runs in the IO monad)

-> IO (RunOutcome Checkpoint (Maybe (Progress result)))

the outcome of the run

Like exploreTreeUntilFirst but with the tree running in IO.

exploreTreeIOUntilFirstStartingFromSource

Arguments

:: Checkpoint

the starting progress

-> ThreadsControllerMonad (FirstMode result) ()

the controller loop, which at the very least must start by increasing the number of workers from 0 to the desired number

-> TreeIO result

the tree (which runs in the IO monad)

-> IO (RunOutcome Checkpoint (Maybe (Progress result)))

the outcome of the run

Like exploreTreeIOUntilFirst but with a starting progress.

exploreTreeTUntilFirstSource

Arguments

:: MonadIO m 
=> (forall α. m α -> IO α)

a function that runs the tree's monad in IO

-> ThreadsControllerMonad (FirstMode result) ()

the controller loop, which at the very least must start by increasing the number of workers from 0 to the desired number

-> TreeT m result

the (impure) tree

-> IO (RunOutcome Checkpoint (Maybe (Progress result)))

the outcome of the run

Like exploreTreeUntilFirst but with a generic impure tree.

exploreTreeTUntilFirstStartingFromSource

Arguments

:: MonadIO m 
=> (forall α. m α -> IO α)

a function that runs the tree's monad in IO

-> Checkpoint

the starting progress

-> ThreadsControllerMonad (FirstMode result) ()

the controller loop, which at the very least must start by increasing the number of workers from 0 to the desired number

-> TreeT m result

the (impure) tree

-> IO (RunOutcome Checkpoint (Maybe (Progress result)))

the outcome of the run

Like exploreTreeTUntilFirst, but with a starting progress.

Stop when sum of results meets condition

Pull

For more details, follow this link: LogicGrowsOnTrees.Parallel.Main

Note that because using these functions entails writing the controller yourself, it is your responsibility to ensure that a global progress update is performed on a regular basis in order to ensure that results are being gathered together at the supervisor.

exploreTreeUntilFoundUsingPullSource

Arguments

:: Monoid result 
=> (result -> Bool)

a condition function that signals when we have found all of the result that we wanted

-> ThreadsControllerMonad (FoundModeUsingPull result) ()

the controller loop, which at the very least must start by increasing the number of workers from 0 to the desired number

-> Tree result

the (pure) tree

-> IO (RunOutcome (Progress result) (Either result (Progress result)))

the outcome of the run

Explore the pure tree until the sum of resuts meets a condition.

exploreTreeUntilFoundUsingPullStartingFromSource

Arguments

:: Monoid result 
=> (result -> Bool)

a condition function that signals when we have found all of the result that we wanted

-> Progress result

the starting progress

-> ThreadsControllerMonad (FoundModeUsingPull result) ()

the controller loop, which at the very least must start by increasing the number of workers from 0 to the desired number

-> Tree result

the (pure) tree

-> IO (RunOutcome (Progress result) (Either result (Progress result)))

the outcome of the run

Like exploreTreeUntilFoundUsingPull but with a starting progress.

exploreTreeIOUntilFoundUsingPullSource

Arguments

:: Monoid result 
=> (result -> Bool)

a condition function that signals when we have found all of the result that we wanted

-> ThreadsControllerMonad (FoundModeUsingPull result) ()

the controller loop, which at the very least must start by increasing the number of workers from 0 to the desired number

-> TreeIO result

the tree (which runs in the IO monad)

-> IO (RunOutcome (Progress result) (Either result (Progress result)))

the outcome of the run

Like exploreTreeUntilFoundUsingPull but with the tree running in IO.

exploreTreeIOUntilFoundUsingPullStartingFromSource

Arguments

:: Monoid result 
=> (result -> Bool)

a condition function that signals when we have found all of the result that we wanted

-> Progress result

the starting progress

-> ThreadsControllerMonad (FoundModeUsingPull result) ()

the controller loop, which at the very least must start by increasing the number of workers from 0 to the desired number

-> TreeIO result

the tree (which runs in the IO monad)

-> IO (RunOutcome (Progress result) (Either result (Progress result)))

the outcome of the run

Like exploreTreeIOUntilFoundUsingPull but with a starting progress.

exploreTreeTUntilFoundUsingPullSource

Arguments

:: (Monoid result, MonadIO m) 
=> (result -> Bool)

a condition function that signals when we have found all of the result that we wanted

-> (forall α. m α -> IO α)

a function that runs the tree's monad in IO

-> ThreadsControllerMonad (FoundModeUsingPull result) ()

the controller loop, which at the very least must start by increasing the number of workers from 0 to the desired number

-> TreeT m result

the (impure) tree

-> IO (RunOutcome (Progress result) (Either result (Progress result)))

the outcome of the run

Like exploreTreeUntilFoundUsingPull but with a generic impure tree.

exploreTreeTUntilFoundUsingPullStartingFromSource

Arguments

:: (Monoid result, MonadIO m) 
=> (result -> Bool)

a condition function that signals when we have found all of the result that we wanted

-> (forall α. m α -> IO α)

a function that runs the tree's monad in IO

-> Progress result

the starting progress

-> ThreadsControllerMonad (FoundModeUsingPull result) ()

the controller loop, which at the very least must start by increasing the number of workers from 0 to the desired number

-> TreeT m result

the (impure) tree

-> IO (RunOutcome (Progress result) (Either result (Progress result)))

the outcome of the run

Like exploreTreeTUntilFoundUsingPull but with a starting progress.

Push

For more details, follow this link: LogicGrowsOnTrees.Parallel.Main

exploreTreeUntilFoundUsingPushSource

Arguments

:: Monoid result 
=> (result -> Bool)

a condition function that signals when we have found all of the result that we wanted

-> ThreadsControllerMonad (FoundModeUsingPush result) ()

the controller loop, which at the very least must start by increasing the number of workers from 0 to the desired number

-> Tree result

the (pure) tree

-> IO (RunOutcome (Progress result) (Either result (Progress result)))

the outcome of the run

Explore the pure tree until the sum of resuts meets a condition.

exploreTreeUntilFoundUsingPushStartingFromSource

Arguments

:: Monoid result 
=> (result -> Bool)

a condition function that signals when we have found all of the result that we wanted

-> Progress result

the starting progress

-> ThreadsControllerMonad (FoundModeUsingPush result) ()

the controller loop, which at the very least must start by increasing the number of workers from 0 to the desired number

-> Tree result

the (pure) tree

-> IO (RunOutcome (Progress result) (Either result (Progress result)))

the outcome of the run

Like exploreTreeUntilFoundUsingPush, but with a starting result.

exploreTreeIOUntilFoundUsingPushSource

Arguments

:: Monoid result 
=> (result -> Bool)

a condition function that signals when we have found all of the result that we wanted

-> ThreadsControllerMonad (FoundModeUsingPush result) ()

the controller loop, which at the very least must start by increasing the number of workers from 0 to the desired number

-> TreeIO result

the tree (which runs in the IO monad)

-> IO (RunOutcome (Progress result) (Either result (Progress result)))

the outcome of the run

Like exploreTreeUntilFoundUsingPush but with the tree running in IO.

exploreTreeIOUntilFoundUsingPushStartingFromSource

Arguments

:: Monoid result 
=> (result -> Bool)

a condition function that signals when we have found all of the result that we wanted

-> Progress result

the starting progress

-> ThreadsControllerMonad (FoundModeUsingPush result) ()

the controller loop, which at the very least must start by increasing the number of workers from 0 to the desired number

-> TreeIO result

the tree (which runs in the IO monad)

-> IO (RunOutcome (Progress result) (Either result (Progress result)))

the outcome of the run

Like exploreTreeIOUntilFoundUsingPush, but with a starting result.

exploreTreeTUntilFoundUsingPushSource

Arguments

:: (Monoid result, MonadIO m) 
=> (result -> Bool)

a condition function that signals when we have found all of the result that we wanted

-> (forall α. m α -> IO α)

a function that runs the tree's monad in IO

-> ThreadsControllerMonad (FoundModeUsingPush result) ()

the controller loop, which at the very least must start by increasing the number of workers from 0 to the desired number

-> TreeT m result

the (impure) tree

-> IO (RunOutcome (Progress result) (Either result (Progress result)))

the outcome of the run

Like exploreTreeUntilFoundUsingPush but with a generic impure tree.

exploreTreeTUntilFoundUsingPushStartingFromSource

Arguments

:: (Monoid result, MonadIO m) 
=> (result -> Bool)

a condition function that signals when we have found all of the result that we wanted

-> (forall α. m α -> IO α)

a function that runs the tree's monad in IO

-> Progress result

the starting progress

-> ThreadsControllerMonad (FoundModeUsingPush result) ()

the controller loop, which at the very least must start by increasing the number of workers from 0 to the desired number

-> TreeT m result

the (impure) tree

-> IO (RunOutcome (Progress result) (Either result (Progress result)))

the outcome of the run

Like exploreTreeTUntilFoundUsingPush, but with a starting progress.

Generic explorer

runExplorerSource

Arguments

:: ExplorationMode exploration_mode

the exploration mode

-> Purity m n

the purity of the tree

-> ProgressFor exploration_mode

the starting progress

-> ThreadsControllerMonad exploration_mode ()

the controller loop, which at the very least must start by increasing the number of workers from 0 to the desired number

-> TreeT m (ResultFor exploration_mode)

the tree

-> IO (RunOutcomeFor exploration_mode)

the outcome of the run

Explores the given tree using multiple threads to achieve parallelism.

This function grants access to all of the functionality of this adapter, but because its generality complicates its use (primarily the fact that the types are dependent on the first parameter) you may find it easier to use one of the specialized functions in the preceding section.