distributed-process-async-0.2.0: Cloud Haskell Async API

Copyright(c) Tim Watson 2012
LicenseBSD3 (see the file LICENSE)
MaintainerTim Watson <watson.timothy@gmail.com>
Stabilityexperimental
Portabilitynon-portable (requires concurrency)
Safe HaskellNone
LanguageHaskell98

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.

Synopsis

Exported types

type AsyncRef = ProcessId Source

A reference to an asynchronous action

data AsyncTask a Source

A task to be performed asynchronously.

Constructors

AsyncTask 

Fields

asyncTask :: Process a

the task to be performed

AsyncRemoteTask 

Fields

asyncTaskDict :: Static (SerializableDict a)

the serializable dict required to spawn a remote process

asyncTaskNode :: NodeId

the node on which to spawn the asynchronous task

asyncTaskProc :: Closure (Process a)

the task to be performed, wrapped in a closure environment

data Async a Source

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.

Instances

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

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.

task :: Process a -> AsyncTask a Source

Wraps a regular Process a as an AsyncTask.

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.

Cancelling asynchronous operations

cancel :: Async a -> Process () Source

Cancel an asynchronous operation.

See Control.Distributed.Process.Platform.Async.

cancelWait :: Serializable a => Async a -> Process (AsyncResult a) Source

Cancel an asynchronous operation and wait for the cancellation to complete.

See Control.Distributed.Process.Platform.Async.

cancelWith :: Serializable b => b -> Async a -> Process () Source

Cancel an asynchronous operation immediately.

See Control.Distributed.Process.Platform.Async.

cancelKill :: String -> Async a -> Process () Source

Like cancelWith but sends a kill instruction instead of an exit.

See Async.

Querying for results

poll :: Serializable a => Async a -> Process (AsyncResult a) Source

Check whether an Async has completed yet.

See Control.Distributed.Process.Platform.Async.

check :: Serializable a => Async a -> Process (Maybe (AsyncResult a)) Source

Like poll but returns Nothing if (poll hAsync) == AsyncPending.

See Control.Distributed.Process.Platform.Async.

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

See Control.Distributed.Process.Platform.Async.

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 => TimeInterval -> [Async a] -> Process (Maybe (AsyncResult a)) Source

Like waitAny but times out after the specified delay.

waitTimeout :: Serializable a => TimeInterval -> Async a -> Process (Maybe (AsyncResult a)) Source

Wait for an asynchronous operation to complete or timeout.

See Control.Distributed.Process.Platform.Async.

waitCancelTimeout :: Serializable a => TimeInterval -> 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 => TimeInterval -> Async a -> Process (AsyncResult a) Source

Wait for an asynchronous operation to complete or timeout.

See Control.Distributed.Process.Platform.Async.

STM versions

pollSTM :: Async a -> STM (Maybe (AsyncResult a)) Source

A version of poll that can be used inside an STM transaction.

waitTimeoutSTM :: Serializable a => TimeInterval -> Async a -> Process (Maybe (AsyncResult a)) Source

As waitTimeout but uses STM directly, which might be more efficient.

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.