Safe Haskell | None |
---|
LogicGrowsOnTrees.Parallel.ExplorationMode
Contents
Description
There are several tasks for which a user may wish to use LogicGrowsOnTrees, such as gathering up all the results in a tree or stopping as soon as the first result is found. Because almost all of the infrastructure required for these different modes is the same, rather than creating a different system for each mode we instead re-use the same system but pass around a mode parameter that dictates its behavior at various points as well as some of the types in the system.
ExplorationMode
is defined using a GADT where each constructor has a
different argument for ExplorationMode
's type parameter; this was
done so that type families can be used to specialized types depending on the
constructor.
- data ExplorationMode exploration_mode where
- AllMode :: Monoid result => ExplorationMode (AllMode result)
- FirstMode :: ExplorationMode (FirstMode result)
- FoundModeUsingPull :: Monoid result => (result -> Bool) -> ExplorationMode (FoundModeUsingPull result)
- FoundModeUsingPush :: Monoid result => (result -> Bool) -> ExplorationMode (FoundModeUsingPush result)
- data AllMode result
- data FirstMode result
- data FoundModeUsingPull result
- data FoundModeUsingPush result
- class HasExplorationMode monad where
- type ExplorationModeFor monad :: *
- type family ResultFor exploration_mode :: *
- type family ProgressFor exploration_mode :: *
- type family FinalResultFor exploration_mode :: *
- type family WorkerIntermediateValueFor exploration_mode :: *
- type family WorkerFinishedProgressFor exploration_mode :: *
- checkpointFromIntermediateProgress :: ExplorationMode exploration_mode -> ProgressFor exploration_mode -> Checkpoint
- initialProgress :: ExplorationMode exploration_mode -> ProgressFor exploration_mode
- initialWorkerIntermediateValue :: ExplorationMode exploration_mode -> WorkerIntermediateValueFor exploration_mode
Types
data ExplorationMode exploration_mode whereSource
A type indicating the mode of the exploration. Note that this is a GADT for which the type parameter is unique to each constructor in order to allow associated types to be specialized based on the value.
Unfortunately Haddock does not seem to support documenting the constructors
of a GADT, so the documentation for each constructor is located at the type
it is tagged with, all of which are defined after the ExplorationMode
type.
Constructors
AllMode :: Monoid result => ExplorationMode (AllMode result) | |
FirstMode :: ExplorationMode (FirstMode result) | |
FoundModeUsingPull :: Monoid result => (result -> Bool) -> ExplorationMode (FoundModeUsingPull result) | |
FoundModeUsingPush :: Monoid result => (result -> Bool) -> ExplorationMode (FoundModeUsingPush result) |
data FoundModeUsingPull result Source
Explore the tree, summing the results, until a condition has been met;
Pull
means that each worker's results will be kept and summed locally
until a request for them has been received from the supervisor, which means
that there might be a period of time where the collectively found results
meet the condition but the system is unaware of this as they are scattered
amongst the workers.
NOTE: If you use this mode then you are responsible for ensuring that a global progress update happens on a regular basis in order to pull the results in from the workers and check to see if the condition has been met; if you do not do this then the run will not terminate until the tree has been fully explored.
data FoundModeUsingPush result Source
Same as FoundModeUsingPull
, but pushes each result to the supervisor as it
is found rather than summing them in the worker until they are requested by
the supervisor, which guarantees that the system will recognize when the
condition has been met as soon as final result needed was found but has the
downside that if there are a large number of results needed then sending
each one could be much more costly then summing them locally and sending the
current total on a regular basis to the supervisor.
Type-classes
class HasExplorationMode monad Source
This class indicates that a monad has information about the current exploration mode tag type that can be extracted from it.
Associated Types
type ExplorationModeFor monad :: *Source
Instances
HasExplorationMode (ThreadsControllerMonad exploration_mode) | |
HasExplorationMode (WorkgroupControllerMonad inner_state exploration_mode) | |
HasExplorationMode (RequestQueueReader exploration_mode worker_id m) |
Type families
type family ResultFor exploration_mode :: *Source
The result type of the tree, i.e. the type of values at the leaves.
type family ProgressFor exploration_mode :: *Source
The type of progress, which keeps track of how much of the tree has already been explored.
type family FinalResultFor exploration_mode :: *Source
The type of the final result of exploring the tree.
type family WorkerIntermediateValueFor exploration_mode :: *Source
The type of the intermediate value being maintained internally by the worker.
type family WorkerFinishedProgressFor exploration_mode :: *Source
The progress type returned by a worker that has finished.
Functions
checkpointFromIntermediateProgress :: ExplorationMode exploration_mode -> ProgressFor exploration_mode -> CheckpointSource
Extracts the Checkpoint
component from a progress value.
initialProgress :: ExplorationMode exploration_mode -> ProgressFor exploration_modeSource
The initial progress at the start of the exploration.
initialWorkerIntermediateValue :: ExplorationMode exploration_mode -> WorkerIntermediateValueFor exploration_modeSource
The initial intermediate value for the worker.