interleave-1.0: Combinators for supporting interleaving of different behaviours

Control.Alternative.Interleave

Description

A module containing interleaving behaviour combinators. See the engage function for some details and examples. A much fuller explanation of this entire library is provided in the forthcoming article in Issue 17 of The Monad Reader which will be published at http://themonadreader.wordpress.com/.

Synopsis

Documentation

data InterleaveT f a Source

This data-type represents potentially-many actions in the f Monad / Alternative that will result in returning a value of type a. See engage for more details.

The Functor instance is straightforward. The <*> operator in the Applicative instance runs the left-hand side and right-hand side alongside each other, and afterwards it applies the left-hand function to the right-hand value.

engage :: Monad f => InterleaveT f a -> f aSource

Offers the given behaviour until either the finite set of actions is exhausted, or one of the explicit termination constructs is triggered.

For example:

 engage $ unlimited p `alongside` unlimited q

will repeatedly offer p and q without ever terminating.

 engage $ upTo 3 p `alongside` upTo 5 q

will do p three times and q 5 times (in any mixed order) then finish.

 engage $ unlimited p `alongside` unlimited q `alongside` endAfter (once r)

will offer p repeatedly and q repeatedly and r, until r happens, at which point the behaviour will end.

 engage $ once p `alongside` endAfter (once q)

will offer p and q; if p happens first it will wait for q, but if q happens first it will finish.

 engage $ once p `alongside` endAfter (once q) `alongside` endAfter (once r)

permits p to happen at most once, while either of q or r happening will finish the call.

All sorts of combinations are possible, but it is important to note that you need at least one endAfter or endWhen event if you ever intend a call involving unlimited (or similar) to finish. Some laws involving engage (ignoring the types and return values) are:

 engage (unlimited p) == forever p
 engage (once p) == Just <$> p
 engage (endAfter (once p)) == engage (once p)
 engage (endAfter (once p) `alongside` endAfter (once q)) == p <|> q

Most other uses of engage and alongside do not reduce down to simple programs, which is of course the attraction of the combinators.

engageMany :: (Monad f, Alternative f) => [InterleaveT f a] -> f [a]Source

Offers all the given behaviours together, and gives back a list of the outcomes.

This is roughly a shorthand for engage . foldr1 alongside, except that if you pass the empty list, you simply get the empty list returned (rather than an error)

alongside :: Alternative f => InterleaveT f a -> InterleaveT f b -> InterleaveT f (a, b)Source

Offers one behaviour alongside another.

This operation is semantically associative and commutative.

alongside_ :: Alternative f => InterleaveT f a -> InterleaveT f b -> InterleaveT f ()Source

Like alongside but discards the results.

alongsideMerge :: (Alternative f, Monoid a) => InterleaveT f a -> InterleaveT f a -> InterleaveT f aSource

Like alongside but merges the results with mappend afterwards.

alongsideMerge a b is equivalent to uncurry mappend <$> (a `alongside` b) and liftA2 mappend a b.

endAfter :: Functor f => InterleaveT f a -> InterleaveT f aSource

Acts like the given item, but when it has no more actions to take, ends the entire call to engage. So this code:

 engage $ unlimited p `alongside` endAfter (once q)

Will terminate after q occurs. In contrast, this code:

 engage $ unlimited p `alongside` once q

will never terminate because it can always offer to perform q.

endWhen :: Functor f => (a -> Bool) -> InterleaveT f a -> InterleaveT f aSource

Acts like the given item, but when the current result value satisfies the given function (i.e. applying the function yields True), ends the entire call to engage.

once :: Functor f => f a -> InterleaveT f (Maybe a)Source

Offers the given behaviour, and when it occurs, does not offer it again. Returns Just the result if the behaviour happens, otherwise gives Nothing.

once m is equivalent to listToMaybe <$> upTo 1 m (and thus also listToMaybe <$> inOrder [m]).

once_ :: Functor f => f a -> InterleaveT f ()Source

Like once but discards the result.

upTo :: Functor f => Int -> f a -> InterleaveT f [a]Source

Offers the given behaviour up to the given number of times, returning a list of the results (in chronological order, earliest first).

upTo n is equivalent to inOrder . replicate n.

upTo_ :: Functor f => Int -> f a -> InterleaveT f ()Source

Like upTo, but discards the results.

inOrder :: Functor f => [f a] -> InterleaveT f [a]Source

Offers the given list of items, in order.

inOrder_ :: Functor f => [f a] -> InterleaveT f ()Source

Like inOrder, but discards the results.

unlimited :: Functor f => f a -> InterleaveT f [a]Source

Repeatedly offers the given behaviour. A list is returned (in chronological order, earliest first) of the results of each occurrence of the behaviour. If you don't want these results, it is better to use unlimited_ to avoid a space leak.

unlimited is equivalent to inOrder . repeat.

unlimited_ :: Functor f => f a -> InterleaveT f ()Source

Like unlimited, but discards the output. Useful if the event is likely to occur many times, and you don't need the results.

unlimitedRecurse :: Functor f => (a -> f (b, a)) -> a -> InterleaveT f [b]Source

Like unlimited, but allows some state (of type a) to be passed from one subsequent call to another, as well as generating the results of type b. To begin with the function (first parameter) will be called with the initial state (second parameter). If chosen, it will return the new state, and a result to be accumulated into the list. The second call to the function will be passed the new state, to then return the even newer state and a second result, and so on.

If you want to use this with the StateT monad transformer from the mtl library, you can call:

 unlimitedRecurse (runStateT myStateAction) initialState
   where
     myStateAction :: StateT s m a
     initialState :: s

unlimitedRecurse_ :: Functor f => (a -> f a) -> a -> InterleaveT f ()Source

Like unlimitedRecurse, but does not accumulate a list of results.

If you want to use this with the StateT monad transformer from the mtl library, you can call:

 unlimitedRecurse (execStateT myStateAction) initialState
   where
     myStateAction :: StateT s m a
     initialState :: s