{-# LANGUAGE OverlappingInstances , UndecidableInstances , ExistentialQuantification , ScopedTypeVariables , MultiParamTypeClasses , FlexibleInstances , FlexibleContexts , TypeSynonymInstances , DeriveDataTypeable , CPP #-} {-# OPTIONS -IControl/Workflow #-} {- | A workflow can be seen as a persistent thread. The workflow monad writes a log that permit to restore the thread at the interrupted point. `step` is the (partial) monad transformer for the Workflow monad. A workflow is defined by its name and, optionally by the key of the single parameter passed. The primitives for starting workflows also restart the workflow when it has been in execution previously. This is the main module that uses the `RefSerialize` paclkage for serialization. Here the constraint @DynSerializer w r a@ is equivalent to @Data.RefSerialize a@ For workflows that uses big structures, for example, documents use this module in combination with the RefSerialize package to define the (de)serialization instances The log size will be reduced. printWFHistory` method will print the structure changes in each step. If instead of RefSerialize, you define read and show instances, there will be no reduction. but still the log will be readable for debugging purposes. for workflows that does not care about this, use the binary alternative: "Control.Workflow.Binary" A small example that print the sequence of integers in te console if you interrupt the progam, when restarted again, it will start from the last printed number @module Main where import Control.Workflow.Text import Control.Concurrent(threadDelay) import System.IO (hFlush,stdout) mcount n= do `step` $ do putStr (show n ++ \" \") hFlush stdout threadDelay 1000000 mcount (n+1) return () -- to disambiguate the return type main= `exec1` \"count\" $ mcount (0 :: Int)@ -} module Control.Workflow.Text ( Workflow -- a useful type name , WorkflowList , PMonadTrans (..) , MonadCatchIO (..) , throw , Indexable(..) -- * Start/restart workflows , start , exec , exec1d , exec1 , wfExec , startWF , restartWorkflows , WFErrors(..) -- * Lifting to the Workflow monad , step , stepControl , unsafeIOtoWF -- * References to intermediate values in the workflow log , WFRef , getWFRef , newWFRef , stepWFRef , readWFRef , writeWFRef -- * Workflow inspect , waitWFActive , getAll , safeFromIDyn , getWFKeys , getWFHistory , waitFor , waitForSTM -- * Persistent timeouts , waitUntilSTM , getTimeoutFlag -- * Trace logging , logWF -- * Termination of workflows , clearRunningFlag , killThreadWF , killWF , delWF , killThreadWF1 , killWF1 , delWF1 , delWFHistory , delWFHistory1 -- * Log writing policy , syncWrite , SyncMode(..) -- * Print log history , printHistory ) where import Control.Workflow.Text.TextDefs #include "Workflow.inc.hs"