inbox-0.2.0: Inbox for asychronous messages
Safe HaskellNone
LanguageHaskell2010

Test.Inbox

Description

Facilitates testing of asynchronouse code.

Example

Assume you have a server that accepts incoming messages and produces responses asynchronously. In order to test it, open a connection to it, and process any incomming message from the server by adding it to the Inbox. Now that we know the messages are all arriving in the inbox, the test can send messages to the server and use takeInbox to wait for expected responses.

Synopsis

Documentation

data Inbox a Source #

An entity holding a number of messages of type a.

newInbox :: IO (Inbox a) Source #

Create an empty Inbox.

putInbox :: forall m a. MonadIO m => Inbox a -> a -> m () Source #

Add a message to the Inbox.

takeInbox :: (MonadIO m, Show a) => Inbox a -> Filter a b -> m b Source #

takeInbox' with a timeout of 3s

takeInbox' :: forall m a b. (MonadIO m, Show a) => Float -> Inbox a -> Filter a b -> m b Source #

Take a single message out of the inbox, waiting for it up to the specified timeout in seconds. It respects the order the messages were inserted into the inbox.

data Filter a b Source #

It is a selector/matcher/extractor with a name. It specifies what message to pick from the Inbox and how to transform it. The name provides for a better error messages. See predicate for a Filter a a that selects an element and does not apply any transformation.

Constructors

Filter Text (a -> Maybe b) 

Instances

Instances details
Arrow Filter Source # 
Instance details

Defined in Test.Inbox

Methods

arr :: (b -> c) -> Filter b c #

first :: Filter b c -> Filter (b, d) (c, d) #

second :: Filter b c -> Filter (d, b) (d, c) #

(***) :: Filter b c -> Filter b' c' -> Filter (b, b') (c, c') #

(&&&) :: Filter b c -> Filter b c' -> Filter b (c, c') #

Category Filter Source # 
Instance details

Defined in Test.Inbox

Methods

id :: forall (a :: k). Filter a a #

(.) :: forall (b :: k) (c :: k) (a :: k). Filter b c -> Filter a b -> Filter a c #

equalTo :: (Eq a, Show a) => a -> Filter a () Source #

A filter that matches messages equal to the given one.

predicate Source #

Arguments

:: Text

name

-> (a -> Bool)

the predicate

-> Filter a a 

A filter that matches messages based on a predicate.

expectEmpty :: Show a => Inbox a -> IO (ErrorOr ()) Source #

Validate that the inbox has no messages inside at the moment.

expectEmpty' :: (Show a, MonadIO m) => Inbox a -> Filter a b -> m () Source #

Validate that the filter does not match anything in the Inbox.