Workflow-0.8.0.7: Workflow patterns over a monad for thread state logging & recovery

Safe HaskellNone

Control.Workflow.Patterns

Contents

Description

This module contains monadic combinators that express some workflow patterns. see the docAprobal.hs example included in the package

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). There is a timeout of seven 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)

The program can be interrupted at any moment. The Workflow monad will restartWorkflows it at the point where it was interrupted.

This example uses queues from Data.Persistent.Queue

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 =  do
      step $ push (quser user) rdoc
      logWF ("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

Synopsis

Low level combinators

split :: (Typeable b, Serialize b, HasFork io, MonadCatchIO io) => [a -> Workflow io b] -> a -> Workflow io [ActionWF b]Source

spawn a list of independent workflow actions with a seed value a The results are reduced by merge or select

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, Typeable a, HasFork io, MonadCatchIO io) => Integer -> (a -> STM 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 kill all the pending workflows and return the list of selected outputs the timeout is in seconds and it is is in the workflow monad, so it is possible to restart the process if interrupted, so it can proceed for years.

This is necessary for the modelization of real-life institutional cycles such are political elections A timeout of 0 means no timeout.

High level conbinators

vote :: (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

sumUp :: (Serialize b, Typeable b, Monoid b, HasFork io, MonadCatchIO io) => Integer -> [a -> Workflow io b] -> a -> Workflow io bSource

sum the outputs of a list of workflows according with its monoid definition

 sumUp timeout actions = vote timeout actions (return . mconcat)

data Select Source

Constructors

Select

select the source output

Discard

Discard the source output

Continue

Continue the source process

FinishDiscard

Discard this output, kill all and return the selected outputs

FinishSelect

Select this output, kill all and return the selected outputs