Copyright | Copyright (c) 2009-2017 David Sorokin <david.sorokin@gmail.com> |
---|---|
License | BSD3 |
Maintainer | David Sorokin <david.sorokin@gmail.com> |
Stability | experimental |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
- Process Monad
- Running Process
- Spawning Processes
- Enqueuing Process
- Creating Process Identifier
- Holding, Interrupting, Passivating and Canceling Process
- Awaiting Signal
- Preemption
- Yield of Process
- Process Timeout
- Parallelizing Processes
- Exception Handling
- Process Priority
- Utilities
- Memoizing Process
- Never Ending Process
- Retrying Computation
- GoTo Statement
- Debugging
Tested with: GHC 8.0.1
A value in the Process
monad represents a discontinuous process that
can suspend in any simulation time point and then resume later in the same
or another time point.
The process of this type can involve the Event
, Dynamics
and Simulation
computations. Moreover, a value in the Process
monad can be run within
the Event
computation.
A value of the ProcessId
type is just an identifier of such a process.
Synopsis
- data ProcessId m
- newtype Process m a = Process (ProcessId m -> Cont m a)
- class ProcessLift t m where
- liftProcess :: Process m a -> t m a
- invokeProcess :: ProcessId m -> Process m a -> Cont m a
- runProcess :: MonadDES m => Process m () -> Event m ()
- runProcessUsingId :: MonadDES m => ProcessId m -> Process m () -> Event m ()
- runProcessInStartTime :: MonadDES m => Process m () -> Simulation m ()
- runProcessInStartTimeUsingId :: MonadDES m => ProcessId m -> Process m () -> Simulation m ()
- runProcessInStopTime :: MonadDES m => Process m () -> Simulation m ()
- runProcessInStopTimeUsingId :: MonadDES m => ProcessId m -> Process m () -> Simulation m ()
- spawnProcess :: MonadDES m => Process m () -> Process m ()
- spawnProcessUsingId :: MonadDES m => ProcessId m -> Process m () -> Process m ()
- spawnProcessWith :: MonadDES m => ContCancellation -> Process m () -> Process m ()
- spawnProcessUsingIdWith :: MonadDES m => ContCancellation -> ProcessId m -> Process m () -> Process m ()
- enqueueProcess :: MonadDES m => Double -> Process m () -> Event m ()
- enqueueProcessUsingId :: MonadDES m => Double -> ProcessId m -> Process m () -> Event m ()
- newProcessId :: MonadDES m => Simulation m (ProcessId m)
- processId :: MonadDES m => Process m (ProcessId m)
- processUsingId :: MonadDES m => ProcessId m -> Process m a -> Process m a
- holdProcess :: MonadDES m => Double -> Process m ()
- interruptProcess :: MonadDES m => ProcessId m -> Event m ()
- processInterrupted :: MonadDES m => ProcessId m -> Event m Bool
- processInterruptionTime :: MonadDES m => ProcessId m -> Event m (Maybe Double)
- passivateProcess :: MonadDES m => Process m ()
- passivateProcessBefore :: MonadDES m => Event m () -> Process m ()
- processPassive :: MonadDES m => ProcessId m -> Event m Bool
- reactivateProcess :: MonadDES m => ProcessId m -> Event m ()
- reactivateProcessImmediately :: MonadDES m => ProcessId m -> Event m ()
- cancelProcessWithId :: MonadDES m => ProcessId m -> Event m ()
- cancelProcess :: MonadDES m => Process m a
- processCancelled :: MonadDES m => ProcessId m -> Event m Bool
- processCancelling :: MonadDES m => ProcessId m -> Signal m ()
- whenCancellingProcess :: MonadDES m => Event m () -> Process m ()
- processAwait :: MonadDES m => Signal m a -> Process m a
- processPreemptionBegin :: MonadDES m => ProcessId m -> Event m ()
- processPreemptionEnd :: MonadDES m => ProcessId m -> Event m ()
- processPreemptionBeginning :: MonadDES m => ProcessId m -> Signal m ()
- processPreemptionEnding :: MonadDES m => ProcessId m -> Signal m ()
- processYield :: MonadDES m => Process m ()
- timeoutProcess :: MonadDES m => Double -> Process m a -> Process m (Maybe a)
- timeoutProcessUsingId :: MonadDES m => Double -> ProcessId m -> Process m a -> Process m (Maybe a)
- processParallel :: MonadDES m => [Process m a] -> Process m [a]
- processParallelUsingIds :: MonadDES m => [(ProcessId m, Process m a)] -> Process m [a]
- processParallel_ :: MonadDES m => [Process m a] -> Process m ()
- processParallelUsingIds_ :: MonadDES m => [(ProcessId m, Process m a)] -> Process m ()
- catchProcess :: (MonadDES m, Exception e) => Process m a -> (e -> Process m a) -> Process m a
- finallyProcess :: MonadDES m => Process m a -> Process m b -> Process m a
- throwProcess :: (MonadDES m, Exception e) => e -> Process m a
- processWithPriority :: MonadDES m => EventPriority -> Process m ()
- zipProcessParallel :: MonadDES m => Process m a -> Process m b -> Process m (a, b)
- zip3ProcessParallel :: MonadDES m => Process m a -> Process m b -> Process m c -> Process m (a, b, c)
- unzipProcess :: MonadDES m => Process m (a, b) -> Simulation m (Process m a, Process m b)
- memoProcess :: MonadDES m => Process m a -> Simulation m (Process m a)
- neverProcess :: MonadDES m => Process m a
- retryProcess :: MonadDES m => String -> Process m a
- transferProcess :: MonadDES m => Process m () -> Process m a
- traceProcess :: MonadDES m => String -> Process m a -> Process m a
Process Monad
Represents a process identifier.
Specifies a discontinuous process that can suspend at any time and then resume later.
Instances
class ProcessLift t m where Source #
A type class to lift the Process
computation into other computations.
liftProcess :: Process m a -> t m a Source #
Lift the specified Process
computation into another computation.
Instances
MonadDES m => ProcessLift Process m Source # | |
Defined in Simulation.Aivika.Trans.Internal.Process liftProcess :: Process m a -> Process m a Source # |
Running Process
runProcess :: MonadDES m => Process m () -> Event m () Source #
Run immediately the process. A new ProcessId
identifier will be
assigned to the process.
To run the process at the specified time, you can use
the enqueueProcess
function.
runProcessUsingId :: MonadDES m => ProcessId m -> Process m () -> Event m () Source #
Run immediately the process with the specified identifier.
It will be more efficient than as you would specify the process identifier
with help of the processUsingId
combinator and then would call runProcess
.
To run the process at the specified time, you can use
the enqueueProcessUsingId
function.
runProcessInStartTime :: MonadDES m => Process m () -> Simulation m () Source #
Run the process in the start time immediately involving all pending
CurrentEvents
in the computation too.
runProcessInStartTimeUsingId :: MonadDES m => ProcessId m -> Process m () -> Simulation m () Source #
Run the process in the start time immediately using the specified identifier
and involving all pending CurrentEvents
in the computation too.
runProcessInStopTime :: MonadDES m => Process m () -> Simulation m () Source #
Run the process in the final simulation time immediately involving all
pending CurrentEvents
in the computation too.
runProcessInStopTimeUsingId :: MonadDES m => ProcessId m -> Process m () -> Simulation m () Source #
Run the process in the final simulation time immediately using
the specified identifier and involving all pending CurrentEvents
in the computation too.
Spawning Processes
spawnProcess :: MonadDES m => Process m () -> Process m () Source #
Spawn the child process. In case of cancelling one of the processes, other process will be cancelled too.
spawnProcessUsingId :: MonadDES m => ProcessId m -> Process m () -> Process m () Source #
Spawn the child process specifying the process identifier. In case of cancelling one of the processes, other process will be cancelled too.
spawnProcessWith :: MonadDES m => ContCancellation -> Process m () -> Process m () Source #
Spawn the child process specifying how the child and parent processes should be cancelled in case of need.
spawnProcessUsingIdWith :: MonadDES m => ContCancellation -> ProcessId m -> Process m () -> Process m () Source #
Spawn the child process specifying how the child and parent processes should be cancelled in case of need.
Enqueuing Process
enqueueProcess :: MonadDES m => Double -> Process m () -> Event m () Source #
Enqueue the process that will be then started at the specified time from the event queue.
enqueueProcessUsingId :: MonadDES m => Double -> ProcessId m -> Process m () -> Event m () Source #
Enqueue the process that will be then started at the specified time from the event queue.
Creating Process Identifier
newProcessId :: MonadDES m => Simulation m (ProcessId m) Source #
Create a new process identifier.
processUsingId :: MonadDES m => ProcessId m -> Process m a -> Process m a Source #
Allow calling the process with the specified identifier.
It creates a nested process when canceling any of two, or raising an
IO
exception in any of the both, affects the Process
computation.
At the same time, the interruption has no such effect as it requires
explicit specifying the ProcessId
identifier of the nested process itself,
that is the nested process cannot be interrupted using only the parent
process identifier.
Holding, Interrupting, Passivating and Canceling Process
holdProcess :: MonadDES m => Double -> Process m () Source #
Hold the process for the specified time period.
interruptProcess :: MonadDES m => ProcessId m -> Event m () Source #
Interrupt a process with the specified identifier if the process
is held by computation holdProcess
.
processInterrupted :: MonadDES m => ProcessId m -> Event m Bool Source #
Test whether the process with the specified identifier was interrupted.
processInterruptionTime :: MonadDES m => ProcessId m -> Event m (Maybe Double) Source #
Return the expected interruption time after finishing the holdProcess
computation,
which value may change if the corresponding process is preempted.
passivateProcess :: MonadDES m => Process m () Source #
Passivate the process.
passivateProcessBefore :: MonadDES m => Event m () -> Process m () Source #
Passivate the process before performing some action.
processPassive :: MonadDES m => ProcessId m -> Event m Bool Source #
Test whether the process with the specified identifier is passivated.
reactivateProcess :: MonadDES m => ProcessId m -> Event m () Source #
Reactivate a process with the specified identifier.
reactivateProcessImmediately :: MonadDES m => ProcessId m -> Event m () Source #
Reactivate a process with the specified identifier immediately.
cancelProcessWithId :: MonadDES m => ProcessId m -> Event m () Source #
Cancel a process with the specified identifier, interrupting it if needed.
cancelProcess :: MonadDES m => Process m a Source #
The process cancels itself.
processCancelled :: MonadDES m => ProcessId m -> Event m Bool Source #
Test whether the process with the specified identifier was cancelled.
processCancelling :: MonadDES m => ProcessId m -> Signal m () Source #
Return a signal that notifies about cancelling the process with the specified identifier.
whenCancellingProcess :: MonadDES m => Event m () -> Process m () Source #
Register a handler that will be invoked in case of cancelling the current process.
Awaiting Signal
Preemption
processPreemptionBegin :: MonadDES m => ProcessId m -> Event m () Source #
Preempt a process with the specified identifier.
processPreemptionEnd :: MonadDES m => ProcessId m -> Event m () Source #
Proceed with the process with the specified identifier after it was preempted with help of preemptProcessBegin
.
processPreemptionBeginning :: MonadDES m => ProcessId m -> Signal m () Source #
Return a signal when the process is preempted.
processPreemptionEnding :: MonadDES m => ProcessId m -> Signal m () Source #
Return a signal when the process is proceeded after it was preempted earlier.
Yield of Process
processYield :: MonadDES m => Process m () Source #
Process Timeout
timeoutProcess :: MonadDES m => Double -> Process m a -> Process m (Maybe a) Source #
Try to run the child process within the specified timeout.
If the process will finish successfully within this time interval then
the result wrapped in Just
will be returned; otherwise, the child process
will be cancelled and Nothing
will be returned.
If an exception is raised in the child process then it is propagated to the parent computation as well.
A cancellation of the child process doesn't lead to cancelling the parent process.
Then Nothing
is returned within the computation.
This is a heavy-weight operation destined for working with arbitrary discontinuous
processes. Please consider using a more light-weight function interruptProcess
or else
cancelProcessWithId
whenever possible.
timeoutProcessUsingId :: MonadDES m => Double -> ProcessId m -> Process m a -> Process m (Maybe a) Source #
Try to run the child process with the given identifier within the specified timeout.
If the process will finish successfully within this time interval then
the result wrapped in Just
will be returned; otherwise, the child process
will be cancelled and Nothing
will be returned.
If an exception is raised in the child process then it is propagated to the parent computation as well.
A cancellation of the child process doesn't lead to cancelling the parent process.
Then Nothing
is returned within the computation.
This is a heavy-weight operation destined for working with arbitrary discontinuous
processes. Please consider using a more light-weight function interruptProcess
or else
cancelProcessWithId
whenever possible.
Parallelizing Processes
processParallel :: MonadDES m => [Process m a] -> Process m [a] Source #
Execute the specified computations in parallel within the current computation and return their results. The cancellation of any of the nested computations affects the current computation. The exception raised in any of the nested computations is propagated to the current computation as well.
Here word parallel
literally means that the computations are
actually executed on a single operating system thread but
they are processed simultaneously by the event queue.
New ProcessId
identifiers will be assigned to the started processes.
processParallelUsingIds :: MonadDES m => [(ProcessId m, Process m a)] -> Process m [a] Source #
Like processParallel
but allows specifying the process identifiers.
It will be more efficient than as you would specify the process identifiers
with help of the processUsingId
combinator and then would call processParallel
.
processParallel_ :: MonadDES m => [Process m a] -> Process m () Source #
Like processParallel
but ignores the result.
processParallelUsingIds_ :: MonadDES m => [(ProcessId m, Process m a)] -> Process m () Source #
Like processParallelUsingIds
but ignores the result.
Exception Handling
catchProcess :: (MonadDES m, Exception e) => Process m a -> (e -> Process m a) -> Process m a Source #
Exception handling within Process
computations.
finallyProcess :: MonadDES m => Process m a -> Process m b -> Process m a Source #
A computation with finalization part.
throwProcess :: (MonadDES m, Exception e) => e -> Process m a Source #
Throw the exception with the further exception handling.
By some reason, an exception raised with help of the standard throw
function
is not handled properly within Process
computation, altough it will be still handled
if it will be wrapped in the IO
monad. Therefore, you should use specialised
functions like the stated one that use the throw
function but within the IO
computation,
which allows already handling the exception.
Process Priority
processWithPriority :: MonadDES m => EventPriority -> Process m () Source #
Proceed with the process that would use the specified event priority.
Utilities
zipProcessParallel :: MonadDES m => Process m a -> Process m b -> Process m (a, b) Source #
Zip two parallel processes waiting for the both.
zip3ProcessParallel :: MonadDES m => Process m a -> Process m b -> Process m c -> Process m (a, b, c) Source #
Zip three parallel processes waiting for their results.
unzipProcess :: MonadDES m => Process m (a, b) -> Simulation m (Process m a, Process m b) Source #
Unzip the process using memoization so that the both returned processes could be applied independently, although they will refer to the same pair of values.
Memoizing Process
memoProcess :: MonadDES m => Process m a -> Simulation m (Process m a) Source #
Memoize the process so that it would always return the same value within the simulation run.
Never Ending Process
neverProcess :: MonadDES m => Process m a Source #
A computation that never computes the result. It behaves like a black hole for
the discontinuous process, although such a process can still be canceled outside
(see cancelProcessWithId
), but then only its finalization parts (see finallyProcess
)
will be called, usually, to release the resources acquired before.
Retrying Computation
retryProcess :: MonadDES m => String -> Process m a Source #
Retry the current computation as possible, using the specified argument
as a SimulationRetry
exception message in case of failure.
GoTo Statement
transferProcess :: MonadDES m => Process m () -> Process m a Source #
Like the GoTo statement it transfers the direction of computation,
but raises an exception when used within catchProcess
or finallyProcess
.