| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Capnp.Rpc.Promise
Description
This module defines a Promise type, represents a value which is not yet
 available, and related utilities.
Synopsis
- data Promise a
- data Fulfiller a
- newPromise :: MonadSTM m => m (Promise a, Fulfiller a)
- newReadyPromise :: MonadSTM m => a -> m (Promise a)
- newPromiseWithCallback :: MonadSTM m => (Either (Parsed Exception) a -> STM ()) -> m (Promise a, Fulfiller a)
- newCallback :: MonadSTM m => (Either (Parsed Exception) a -> STM ()) -> m (Fulfiller a)
- fulfill :: MonadSTM m => Fulfiller a -> a -> m ()
- breakPromise :: MonadSTM m => Fulfiller a -> Parsed Exception -> m ()
- breakOrFulfill :: MonadSTM m => Fulfiller a -> Either (Parsed Exception) a -> m ()
- data ErrAlreadyResolved = ErrAlreadyResolved
- wait :: MonadSTM m => Promise a -> m a
Documentation
A promise is a value that may not be ready yet.
Creating promises
newPromise :: MonadSTM m => m (Promise a, Fulfiller a) Source #
Create a new promise and an associated fulfiller.
newReadyPromise :: MonadSTM m => a -> m (Promise a) Source #
Create a promise that is already fulfilled, with the given value.
newPromiseWithCallback :: MonadSTM m => (Either (Parsed Exception) a -> STM ()) -> m (Promise a, Fulfiller a) Source #
Create a new promise which also excecutes an STM action when it is resolved.
newCallback :: MonadSTM m => (Either (Parsed Exception) a -> STM ()) -> m (Fulfiller a) Source #
Like newPromiseWithCallback, but doesn't return the promise.
Fulfilling or breaking promises
fulfill :: MonadSTM m => Fulfiller a -> a -> m () Source #
Fulfill a promise by supplying the specified value. It is an error to
 call fulfill if the promise has already been fulfilled (or broken).
breakPromise :: MonadSTM m => Fulfiller a -> Parsed Exception -> m () Source #
Break a promise. When the user of the promise executes wait, the
 specified exception will be raised. It is an error to call breakPromise
 if the promise has already been fulfilled (or broken).
breakOrFulfill :: MonadSTM m => Fulfiller a -> Either (Parsed Exception) a -> m () Source #
breakOrFulfill calls either breakPromise or fulfill, depending
 on the argument.
data ErrAlreadyResolved Source #
An exception thrown if breakPromise or fulfill is called on an
 already-resolved fulfiller.
Constructors
| ErrAlreadyResolved | 
Instances
| Exception ErrAlreadyResolved Source # | |
| Defined in Capnp.Rpc.Promise Methods toException :: ErrAlreadyResolved -> SomeException # fromException :: SomeException -> Maybe ErrAlreadyResolved # | |
| Show ErrAlreadyResolved Source # | |
| Defined in Capnp.Rpc.Promise Methods showsPrec :: Int -> ErrAlreadyResolved -> ShowS # show :: ErrAlreadyResolved -> String # showList :: [ErrAlreadyResolved] -> ShowS # | |