{-# OPTIONS -XDeriveDataTypeable #-} -- this program imput numbers and calculate their factorials. The workflow control a record all the inputs and outputs -- so that when the program restart, all the previous results are shown. -- if the program abort by a runtime error or a power failure, the program will still work -- enter 0 for exit and finalize the workflow (all the intermediate data will be erased) -- enter any alphanumeric character for aborting and then re-start. module Main where import Control.Workflow import Data.TCache.Dynamic import Data.Typeable fact 0 =1 fact n= n * fact (n-1) {- this is the origina program without workflow factorials= do print "give me a number" str<- getLine let n= read str :: Integer let fct= fact n print fct factorials main1= factorials -} -- now the workflow versiĆ³n data Fact= Fact Integer Integer deriving (Read, Show, Typeable) instance IResource Fact where keyResource _= "lastfact" serialize= show deserialize= read factorialsWF _= do all <- getAll syncWrite True undefined undefined -- default anyway unsafeIOtoWF $ putStrLn "Factorials calculated so far:" unsafeIOtoWF $ putStrLn $ concatMap (\(Fact n fct)-> "number "++ show n ++ " factorial is "++ show fct++ "\n") all factLoop (Fact 0 1) where factLoop fct= do nf <- plift $ do putStrLn "give me a number if you enter a letter or 0, the program will abort. Then, please restart to see how the program continues" str<- getLine let n= read str :: Integer -- if you enter alphanumeric characters the program will abort. please restart let fct= fact n print fct return $ Fact n fct case nf of Fact 0 _ -> do unsafeIOtoWF $ print "bye" return (Fact 0 0) _ -> factLoop nf main = do registerType :: IO Fact -- register this datatype startWF "factorials" (Fact 0 0) [("factorials",factorialsWF)]