Safe Haskell | Safe-Infered |
---|
This module contains monadic combinators that express some workflow patterns. see the docAprobal.hs example included in the package
Here the constraint `DynSerializer w r a` is equivalent to `Data.Refserialize a` This version permits optimal (de)serialization if you store in the queue different versions of largue structures, for example, documents. You must define the right RefSerialize instance however. See an example in docAprobal.hs incuded in the paclkage. Alternatively you can use Data.Binary serlializatiion with Control.Workflow.Binary.Patterns
EXAMPLE:
This fragment below describes the approbal procedure of a document. First the document reference is sent to a list of bosses trough a queue. ithey return a boolean in a return queue ( askUser) the booleans are summed up according with a monoid instance (sumUp)
if the resullt is false, the correctWF workflow is executed If the result is True, the pipeline continues to the next stage (checkValidated)
the next stage is the same process with a new list of users (superbosses). This time, there is a timeout of 7 days. the result of the users that voted is summed up according with the same monoid instance
if the result is true the document is added to the persistent list of approbed documents if the result is false, the document is added to the persistent list of rejectec documents (checlkValidated1)
docApprobal :: Document -> Workflow IO () docApprobal doc =getWFRef
>>= docApprobal1 docApprobal1 rdoc= return True >>= log "requesting approbal from bosses" >>=sumUp
0 (map (askUser doc rdoc) bosses) >>= checkValidated >>= log "requesting approbal from superbosses or timeout" >>=sumUp
(7*60*60*24) (map(askUser doc rdoc) superbosses) >>= checkValidated1 askUser _ _ user False = return False askUser doc rdoc user True = dostep
$push
(quser user) rdoclogWF
(wait for any response from the user: ++ user)step
.pop
$ qdocApprobal (title doc) log txt x =logWF
txt >> return x checkValidated :: Bool ->Workflow
IO Bool checkValidated val = case val of False -> correctWF (title doc) rdoc >> return False _ -> return True checkValidated1 :: Bool -> Workflow IO () checkValidated1 val = step $ do case val of False ->push
qrejected doc _ ->push
qapproved doc mapM (u ->deleteFromQueue (quser u) rdoc) superbosses
- split :: (Typeable b, Serialize b, HasFork io, MonadCatchIO io) => [a -> Workflow io b] -> a -> Workflow io [ActionWF b]
- merge :: (MonadIO io, Typeable a, Typeable b, Serialize a, Serialize b) => ([a] -> io b) -> [ActionWF a] -> Workflow io b
- select :: (Serialize a, Serialize [a], Typeable a, HasFork io, MonadCatchIO io) => Integer -> (a -> io Select) -> [ActionWF a] -> Workflow io [a]
- vote :: (Serialize b, Serialize [b], Typeable b, HasFork io, MonadCatchIO io) => Integer -> [a -> Workflow io b] -> ([b] -> Workflow io c) -> a -> Workflow io c
- sumUp :: (Serialize b, Serialize [b], Typeable b, Monoid b, HasFork io, MonadCatchIO io) => Integer -> [a -> Workflow io b] -> a -> Workflow io b
- data Select
- = Select
- | Discard
- | FinishDiscard
- | FinishSelect
Low level combinators
split :: (Typeable b, Serialize b, HasFork io, MonadCatchIO io) => [a -> Workflow io b] -> a -> Workflow io [ActionWF b]Source
merge :: (MonadIO io, Typeable a, Typeable b, Serialize a, Serialize b) => ([a] -> io b) -> [ActionWF a] -> Workflow io bSource
wait for the results and apply the cond to produce a single output in the Workflow monad
select :: (Serialize a, Serialize [a], Typeable a, HasFork io, MonadCatchIO io) => Integer -> (a -> io Select) -> [ActionWF a] -> Workflow io [a]Source
select the outputs of the workflows produced by split
constrained within a timeout.
The check filter, can select , discard or finish the entire computation before
the timeout is reached. When the computation finalizes, it stop all
the pending workflows and return the list of selected outputs
the timeout is in seconds and is no limited to Int values, so it can last for years.
This is necessary for the modelization of real-life institutional cycles such are political elections timeout of 0 means no timeout.
High level conbinators
vote :: (Serialize b, Serialize [b], Typeable b, HasFork io, MonadCatchIO io) => Integer -> [a -> Workflow io b] -> ([b] -> Workflow io c) -> a -> Workflow io cSource
spawn a list of workflows and reduces the results according with the comp parameter within a given timeout
vote timeout actions comp x= split actions x >>= select timeout (const $ return Select) >>= comp