| Safe Haskell | Safe-Inferred | 
|---|
Control.Concurrent.CHP.Behaviours
Description
A module containing CHP behaviours.  See offer for details.
- data CHPBehaviour a
- offer :: CHPBehaviour a -> CHP a
- offerAll :: [CHPBehaviour a] -> CHP [a]
- alongside :: CHPBehaviour a -> CHPBehaviour b -> CHPBehaviour (a, b)
- alongside_ :: CHPBehaviour a -> CHPBehaviour b -> CHPBehaviour ()
- endWhen :: CHP a -> CHPBehaviour (Maybe a)
- once :: CHP a -> CHPBehaviour (Maybe a)
- upTo :: Int -> CHP a -> CHPBehaviour [a]
- repeatedly :: forall a. CHP a -> CHPBehaviour [a]
- repeatedly_ :: CHP a -> CHPBehaviour ()
- repeatedlyRecurse :: forall a b. (a -> CHP (b, a)) -> a -> CHPBehaviour [b]
- repeatedlyRecurse_ :: forall a. (a -> CHP a) -> a -> CHPBehaviour ()
Documentation
data CHPBehaviour a Source
This data represents a behaviour (potentially repeated) that will result in
 returning a value of type a.  See offer for more details.
Instances
offer :: CHPBehaviour a -> CHP aSource
Offers the given behaviour until finished.
For example,
offer $ repeatedly p `alongside` repeatedly q
will repeatedly offer p and q without ever terminating. This:
offer $ repeatedly p `alongside` repeatedly q `alongside` endWhen r
will offer p repeatedly and q repeatedly and r, until r happens, at which point the behaviour will end. This:
offer $ once p `alongside` endWhen q
will offer p and q; if p happens first it will wait for q, but if q happens first it will finish. This:
offer $ once p `alongside` endWhen q `alongside` endWhen 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 endWhen event if you ever intend the call to finish.  Some
 laws involving offer (ignoring the types and return values) are:
offer (repeatedly p) == forever p offer (once p) == p >> stop -- i.e. it does not finish offer (endWhen q) == Just <$> q offer (endWhen p `alongside` endWhen q) == p <-> q offer (once p `alongside` endWhen q) == (p >> q) <-> q
Most other uses of offer and alongside do not reduce down to simple CHP
 programs, which is of course their attraction.
offerAll :: [CHPBehaviour a] -> CHP [a]Source
Offers all the given behaviours together, and gives back a list of the outcomes.
This is roughly a shorthand for offer . foldl1 alongside, except that if you
 pass the empty list, you simply get the empty list returned (rather than an
 error)
alongside :: CHPBehaviour a -> CHPBehaviour b -> CHPBehaviour (a, b)Source
Offers one behaviour alongside another, combining their semantics.  See offer.
This operation is semantically associative and commutative.
alongside_ :: CHPBehaviour a -> CHPBehaviour b -> CHPBehaviour ()Source
endWhen :: CHP a -> CHPBehaviour (Maybe a)Source
Offers the given behaviour, and when it occurs, ends the entire call to offer.
  Returns Just the result if the behaviour happens, otherwise gives Nothing.
once :: CHP a -> CHPBehaviour (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 is different to endWhen because the latter terminates the call to offer
 regardless of other behaviours, whereas once does not terminate the call to offer,
 it just won't be offered again during the call to offer.  Thus if you only
 offer some once items without any endWhen, then after all the once events
 have happened, the process will deadlock.
once m can be thought of as a shortcut for listToMaybe $ upTo1 m
upTo :: Int -> CHP a -> CHPBehaviour [a]Source
repeatedly :: forall a. CHP a -> CHPBehaviour [a]Source
repeatedly_ :: CHP a -> CHPBehaviour ()Source
Like repeatedly, but discards the output.  Useful if the event is likely
 to occur a lot, and you don't need the results.
repeatedlyRecurse :: forall a b. (a -> CHP (b, a)) -> a -> CHPBehaviour [b]Source
Like repeatedly, 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:
 repeatedlyRecurse (runStateT myStateAction) initialState
   where
     myStateAction :: StateT s CHP a
     initialState :: s
repeatedlyRecurse_ :: forall a. (a -> CHP a) -> a -> CHPBehaviour ()Source
Like repeatedlyRecurse, 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:
 repeatedlyRecurse (execStateT myStateAction) initialState
   where
     myStateAction :: StateT s CHP a
     initialState :: s