| Copyright | (c) Tim Watson 2012 | 
|---|---|
| License | BSD3 (see the file LICENSE) | 
| Maintainer | Tim Watson <watson.timothy@gmail.com> | 
| Stability | experimental | 
| Portability | non-portable (requires concurrency) | 
| Safe Haskell | None | 
| Language | Haskell98 | 
Control.Distributed.Process.Async
Contents
Description
This API provides a means for spawning asynchronous operations, waiting for their results, cancelling them and various other utilities. Asynchronous operations can be executed on remote nodes.
- Asynchronous Operations
There is an implicit contract for async workers; Workers must exit
 normally (i.e., should not call the exit, die or terminate
 Cloud Haskell primitives), otherwise the AsyncResult will end up being
 AsyncFailed DiedException instead of containing the result.
Portions of this file are derived from the Control.Concurrent.Async
 module, from the async package written by Simon Marlow.
- type AsyncRef = ProcessId
- data AsyncTask a- = AsyncTask { }
- | AsyncRemoteTask { - asyncTaskDict :: Static (SerializableDict a)
- asyncTaskNode :: NodeId
- asyncTaskProc :: Closure (Process a)
 
 
- data Async a
- data AsyncResult a
- async :: Serializable a => AsyncTask a -> Process (Async a)
- asyncLinked :: Serializable a => AsyncTask a -> Process (Async a)
- task :: Process a -> AsyncTask a
- remoteTask :: Static (SerializableDict a) -> NodeId -> Closure (Process a) -> AsyncTask a
- monitorAsync :: Async a -> Process MonitorRef
- asyncWorker :: Async a -> ProcessId
- cancel :: Async a -> Process ()
- cancelWait :: Serializable a => Async a -> Process (AsyncResult a)
- cancelWith :: Serializable b => b -> Async a -> Process ()
- cancelKill :: String -> Async a -> Process ()
- poll :: Serializable a => Async a -> Process (AsyncResult a)
- check :: Serializable a => Async a -> Process (Maybe (AsyncResult a))
- wait :: Async a -> Process (AsyncResult a)
- waitAny :: Serializable a => [Async a] -> Process (Async a, AsyncResult a)
- waitAnyTimeout :: Serializable a => Int -> [Async a] -> Process (Maybe (AsyncResult a))
- waitTimeout :: Serializable a => Int -> Async a -> Process (Maybe (AsyncResult a))
- waitCancelTimeout :: Serializable a => Int -> Async a -> Process (AsyncResult a)
- waitCheckTimeout :: Serializable a => Int -> Async a -> Process (AsyncResult a)
- pollSTM :: Async a -> STM (Maybe (AsyncResult a))
- waitAnyCancel :: Serializable a => [Async a] -> Process (Async a, AsyncResult a)
- waitEither :: Async a -> Async b -> Process (Either (AsyncResult a) (AsyncResult b))
- waitEither_ :: Async a -> Async b -> Process ()
- waitBoth :: Async a -> Async b -> Process (AsyncResult a, AsyncResult b)
Exported types
A task to be performed asynchronously.
Constructors
| AsyncTask | |
| AsyncRemoteTask | |
| Fields 
 | |
An handle for an asynchronous action spawned by async.
 Asynchronous operations are run in a separate process, and
 operations are provided for waiting for asynchronous actions to
 complete and obtaining their results (see e.g. wait).
Handles of this type cannot cross remote boundaries, nor are they
 Serializable.
data AsyncResult a Source #
Represents the result of an asynchronous action, which can be in one of several states at any given time.
Constructors
| AsyncDone a | a completed action and its result | 
| AsyncFailed DiedReason | a failed action and the failure reason | 
| AsyncLinkFailed DiedReason | a link failure and the reason | 
| AsyncCancelled | a cancelled action | 
| AsyncPending | a pending action (that is still running) | 
Instances
| Functor AsyncResult Source # | |
| Eq a => Eq (AsyncResult a) Source # | |
| Show a => Show (AsyncResult a) Source # | |
| Generic (AsyncResult a) Source # | |
| Serializable a => Binary (AsyncResult a) Source # | |
| type Rep (AsyncResult a) Source # | |
Spawning asynchronous operations
async :: Serializable a => AsyncTask a -> Process (Async a) Source #
Spawns an asynchronous action and returns a handle to it, which can be used to obtain its status and/or result or interact with it (using the API exposed by this module).
asyncLinked :: Serializable a => AsyncTask a -> Process (Async a) Source #
This is a useful variant of async that ensures an Async task is
 never left running unintentionally. We ensure that if the caller's process
 exits, that the worker is killed.
There is currently a contract for async workers, that they should
 exit normally (i.e., they should not call the exit or kill with their own
 ProcessId nor use the terminate primitive to cease functining), otherwise
 the AsyncResult will end up being AsyncFailed DiedException instead of
 containing the desired result.
remoteTask :: Static (SerializableDict a) -> NodeId -> Closure (Process a) -> AsyncTask a Source #
Wraps the components required and builds a remote AsyncTask.
monitorAsync :: Async a -> Process MonitorRef Source #
Given an Async handle, monitor the worker process.
asyncWorker :: Async a -> ProcessId Source #
Provides the pid of the worker process performing the async operation.
Cancelling asynchronous operations
cancelWait :: Serializable a => Async a -> Process (AsyncResult a) Source #
Cancel an asynchronous operation and wait for the cancellation to complete.
cancelWith :: Serializable b => b -> Async a -> Process () Source #
Cancel an asynchronous operation immediately.
cancelKill :: String -> Async a -> Process () Source #
Like cancelWith but sends a kill instruction instead of an exit.
Querying for results
poll :: Serializable a => Async a -> Process (AsyncResult a) Source #
Check whether an Async has completed yet.
check :: Serializable a => Async a -> Process (Maybe (AsyncResult a)) Source #
wait :: Async a -> Process (AsyncResult a) Source #
Wait for an asynchronous action to complete, and return its
 value. The result (which can include failure and/or cancellation) is
 encoded by the AsyncResult type.
wait = liftIO . atomically . waitSTM
waitAny :: Serializable a => [Async a] -> Process (Async a, AsyncResult a) Source #
Wait for any of the supplied Asyncs to complete. If multiple
 Asyncs complete, then the value returned corresponds to the first
 completed Async in the list.
NB: Unlike AsyncChan, Async does not discard its AsyncResult once
 read, therefore the semantics of this function are different to the
 former. Specifically, if asyncs = [a1, a2, a3] and (AsyncDone _) = a1
 then the remaining a2, a3 will never be returned by waitAny.
Waiting with timeouts
waitAnyTimeout :: Serializable a => Int -> [Async a] -> Process (Maybe (AsyncResult a)) Source #
Like waitAny but times out after the specified delay.
waitTimeout :: Serializable a => Int -> Async a -> Process (Maybe (AsyncResult a)) Source #
Wait for an asynchronous operation to complete or timeout.
waitCancelTimeout :: Serializable a => Int -> Async a -> Process (AsyncResult a) Source #
Wait for an asynchronous operation to complete or timeout.
 If it times out, then cancelWait the async handle.
waitCheckTimeout :: Serializable a => Int -> Async a -> Process (AsyncResult a) Source #
Wait for an asynchronous operation to complete or timeout.
STM versions
pollSTM :: Async a -> STM (Maybe (AsyncResult a)) Source #
A version of poll that can be used inside an STM transaction.
waitAnyCancel :: Serializable a => [Async a] -> Process (Async a, AsyncResult a) Source #
Like waitAny, but also cancels the other asynchronous
 operations as soon as one has completed.
waitEither :: Async a -> Async b -> Process (Either (AsyncResult a) (AsyncResult b)) Source #
Wait for the first of two Asyncs to finish.
waitEither_ :: Async a -> Async b -> Process () Source #
Like waitEither, but the result is ignored.
waitBoth :: Async a -> Async b -> Process (AsyncResult a, AsyncResult b) Source #
Waits for both Asyncs to finish.