| Copyright | Copyright (c) 2009-2015, David Sorokin <david.sorokin@gmail.com> | 
|---|---|
| License | BSD3 | 
| Maintainer | David Sorokin <david.sorokin@gmail.com> | 
| Stability | experimental | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Simulation.Aivika.Process
Contents
Description
Tested with: GHC 7.10.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.
The characteristic property of the Process type is function holdProcess
 that suspends the current process for the specified time interval.
- data ProcessId
- data Process a
- class ProcessLift m where- liftProcess :: Process a -> m a
 
- runProcess :: Process () -> Event ()
- runProcessUsingId :: ProcessId -> Process () -> Event ()
- runProcessInStartTime :: Process () -> Simulation ()
- runProcessInStartTimeUsingId :: ProcessId -> Process () -> Simulation ()
- runProcessInStopTime :: Process () -> Simulation ()
- runProcessInStopTimeUsingId :: ProcessId -> Process () -> Simulation ()
- spawnProcess :: Process () -> Process ()
- spawnProcessUsingId :: ProcessId -> Process () -> Process ()
- spawnProcessWith :: ContCancellation -> Process () -> Process ()
- spawnProcessUsingIdWith :: ContCancellation -> ProcessId -> Process () -> Process ()
- enqueueProcess :: Double -> Process () -> Event ()
- enqueueProcessUsingId :: Double -> ProcessId -> Process () -> Event ()
- newProcessId :: Simulation ProcessId
- processId :: Process ProcessId
- processUsingId :: ProcessId -> Process a -> Process a
- holdProcess :: Double -> Process ()
- interruptProcess :: ProcessId -> Event ()
- processInterrupted :: ProcessId -> Event Bool
- passivateProcess :: Process ()
- processPassive :: ProcessId -> Event Bool
- reactivateProcess :: ProcessId -> Event ()
- cancelProcessWithId :: ProcessId -> Event ()
- cancelProcess :: Process a
- processCancelled :: ProcessId -> Event Bool
- processCancelling :: ProcessId -> Signal ()
- whenCancellingProcess :: Event () -> Process ()
- processAwait :: Signal a -> Process a
- processPreemptionBeginning :: ProcessId -> Signal ()
- processPreemptionEnding :: ProcessId -> Signal ()
- processYield :: Process ()
- timeoutProcess :: Double -> Process a -> Process (Maybe a)
- timeoutProcessUsingId :: Double -> ProcessId -> Process a -> Process (Maybe a)
- processParallel :: [Process a] -> Process [a]
- processParallelUsingIds :: [(ProcessId, Process a)] -> Process [a]
- processParallel_ :: [Process a] -> Process ()
- processParallelUsingIds_ :: [(ProcessId, Process a)] -> Process ()
- catchProcess :: Exception e => Process a -> (e -> Process a) -> Process a
- finallyProcess :: Process a -> Process b -> Process a
- throwProcess :: Exception e => e -> Process a
- zipProcessParallel :: Process a -> Process b -> Process (a, b)
- zip3ProcessParallel :: Process a -> Process b -> Process c -> Process (a, b, c)
- unzipProcess :: Process (a, b) -> Simulation (Process a, Process b)
- memoProcess :: Process a -> Simulation (Process a)
- neverProcess :: Process a
- traceProcess :: String -> Process a -> Process a
Process Monad
Specifies a discontinuous process that can suspend at any time and then resume later.
class ProcessLift m where Source
A type class to lift the Process computation to other computations.
Methods
liftProcess :: Process a -> m a Source
Lift the specified Process computation to another computation.
Instances
Running Process
runProcess :: Process () -> Event () 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 :: ProcessId -> Process () -> Event () 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 :: Process () -> Simulation () Source
Run the process in the start time immediately involving all pending
 CurrentEvents in the computation too.
runProcessInStartTimeUsingId :: ProcessId -> Process () -> Simulation () Source
Run the process in the start time immediately using the specified identifier
 and involving all pending CurrentEvents in the computation too.
runProcessInStopTime :: Process () -> Simulation () Source
Run the process in the final simulation time immediately involving all
 pending CurrentEvents in the computation too.
runProcessInStopTimeUsingId :: ProcessId -> Process () -> Simulation () 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 :: Process () -> Process () Source
Spawn the child process. In case of cancelling one of the processes, other process will be cancelled too.
spawnProcessUsingId :: ProcessId -> Process () -> Process () Source
Spawn the child process with the specified process identifier. In case of cancelling one of the processes, other process will be cancelled too.
spawnProcessWith :: ContCancellation -> Process () -> Process () Source
Spawn the child process specifying how the child and parent processes should be cancelled in case of need.
spawnProcessUsingIdWith :: ContCancellation -> ProcessId -> Process () -> Process () Source
Spawn the child process specifying how the child and parent processes should be cancelled in case of need.
Enqueueing Process
enqueueProcess :: Double -> Process () -> Event () Source
Enqueue the process that will be then started at the specified time from the event queue.
enqueueProcessUsingId :: Double -> ProcessId -> Process () -> Event () Source
Enqueue the process that will be then started at the specified time from the event queue.
Creating Process Identifier
newProcessId :: Simulation ProcessId Source
Create a new process identifier.
processUsingId :: ProcessId -> Process a -> Process 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 :: Double -> Process () Source
Hold the process for the specified time period.
interruptProcess :: ProcessId -> Event () Source
Interrupt a process with the specified identifier if the process
 is held by computation holdProcess.
processInterrupted :: ProcessId -> Event Bool Source
Test whether the process with the specified identifier was interrupted.
passivateProcess :: Process () Source
Passivate the process.
processPassive :: ProcessId -> Event Bool Source
Test whether the process with the specified identifier is passivated.
reactivateProcess :: ProcessId -> Event () Source
Reactivate a process with the specified identifier.
cancelProcessWithId :: ProcessId -> Event () Source
Cancel a process with the specified identifier, interrupting it if needed.
cancelProcess :: Process a Source
The process cancels itself.
processCancelled :: ProcessId -> Event Bool Source
Test whether the process with the specified identifier was cancelled.
processCancelling :: ProcessId -> Signal () Source
Return a signal that notifies about cancelling the process with the specified identifier.
whenCancellingProcess :: Event () -> Process () Source
Register a handler that will be invoked in case of cancelling the current process.
Awaiting Signal
processAwait :: Signal a -> Process a Source
Await the signal.
Preemption
processPreemptionBeginning :: ProcessId -> Signal () Source
Return a signal when the process is preempted.
processPreemptionEnding :: ProcessId -> Signal () Source
Return a signal when the process is proceeded after it was preempted earlier.
Yield of Process
processYield :: Process () Source
Process Timeout
timeoutProcess :: Double -> Process a -> Process (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.
timeoutProcessUsingId :: Double -> ProcessId -> Process a -> Process (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.
Parallelizing Processes
processParallel :: [Process a] -> Process [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 :: [(ProcessId, Process a)] -> Process [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_ :: [Process a] -> Process () Source
Like processParallel but ignores the result.
processParallelUsingIds_ :: [(ProcessId, Process a)] -> Process () Source
Like processParallelUsingIds but ignores the result.
Exception Handling
catchProcess :: Exception e => Process a -> (e -> Process a) -> Process a Source
Exception handling within Process computations.
finallyProcess :: Process a -> Process b -> Process a Source
A computation with finalization part.
throwProcess :: Exception e => e -> Process 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.
Utilities
zipProcessParallel :: Process a -> Process b -> Process (a, b) Source
Zip two parallel processes waiting for the both.
zip3ProcessParallel :: Process a -> Process b -> Process c -> Process (a, b, c) Source
Zip three parallel processes waiting for their results.
unzipProcess :: Process (a, b) -> Simulation (Process a, Process 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 :: Process a -> Simulation (Process a) Source
Memoize the process so that it would always return the same value within the simulation run.
Never Ending Process
neverProcess :: Process 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.
Debugging
traceProcess :: String -> Process a -> Process a Source
Show the debug message with the current simulation time.