transient-0.5.8: composing programs with multithreading, events and distributed computing

Safe HaskellNone
LanguageHaskell2010

Transient.Backtrack

Contents

Description

Transient implements an event handling mechanism ("backtracking") which allows registration of one or more event handlers to be executed when an event occurs. This common underlying mechanism called is used to handle three different types of events:

  • User initiated actions to run undo and retry actions on failures
  • Finalization actions to run at the end of a task
  • Exception handlers to run when exceptions are raised

Backtracking works seamlessly across thread boundaries. The freedom to put the undo, exception handling and finalization code where we want it allows us to write modular and composable code.

Note that backtracking (undo, finalization or exception handling) does not change or automatically roll back the user defined state in any way. It only executes the user installed handlers. State changes are only caused via user defined actions. Any state changes done within the backtracking actions are accumulated on top of the user state as it was when backtracking started. This example prints the final state as "world".

import Transient.Base (keep, setState, getState)
import Transient.Backtrack (onUndo, undo)
import Control.Monad.IO.Class (liftIO)

main = keep $ do
    setState "hello"
    oldState <- getState

    liftIO (putStrLn "Register undo") `onUndo` (do
        curState <- getState
        liftIO $ putStrLn $ "Final state: "  ++ curState
        liftIO $ putStrLn $ "Old state: "    ++ oldState)

    setState "world" >> undo >> return ()

See this blog post for more details.

Synopsis

Multi-track Undo

Transient allows you to pair an action with an undo action (onBack). As actions are executed the corresponding undo actions are saved. At any point an undo can be triggered which executes all the undo actions registered till now in reverse order. At any point, an undo action can decide to resume forward execution by using forward.

Multiple independent undo tracks can be defined for different use cases. An undo track is identified by a user defined data type. The data type of each track must be distinct.

import Control.Concurrent (threadDelay)
import Control.Monad.IO.Class (liftIO)
import Transient.Base (keep)
import Transient.Backtrack (onBack, forward, back)

data Track = Track String deriving Show

main = keep $ do
    step 1 >> goForward >> step 2 >> step 3 >> back (Track "Failed") >> return ()
    where
          step n = liftIO (putStrLn $ "Execute Step: " ++ show n)
                   `onBack`
                   (Track r) -> liftIO (putStrLn $ show r ++ " Undo Step: " ++ show n)

          goForward = liftIO (putStrLn "Turning point")
                      `onBack` (Track r) ->
                                    forward (Track r)
                                    >> (liftIO $ threadDelay 1000000
                                                >> putStrLn "Going forward...")

onBack :: (Typeable b, Show b) => TransientIO a -> (b -> TransientIO a) -> TransientIO a Source #

Run the action in the first parameter and register the second parameter as the undo action. On undo (back) the second parameter is called with the undo track id as argument.

back :: (Typeable b, Show b) => b -> TransientIO a Source #

Start the undo process for the given undo track id. Performs all the undo actions registered till now in reverse order. An undo action can use forward to stop the undo process and resume forward execution. If there are no more undo actions registered execution stops and a stop action is returned.

forward :: (Typeable b, Show b) => b -> TransIO () Source #

For a given undo track id, stop executing more backtracking actions and resume normal execution in the forward direction. Used inside an undo action.

backCut :: (Typeable b, Show b) => b -> TransientIO () Source #

Delete all the undo actions registered till now for the given track id.

Default Track Undo

A default undo track with the track id of type () is provided. APIs for the default track are simpler as they do not require the track id argument.

import Control.Concurrent (threadDelay)
import Control.Monad.IO.Class (liftIO)
import Transient.Base (keep)
import Transient.Backtrack (onUndo, undo, retry)

main = keep $ do
    step 1 >> tryAgain >> step 2 >> step 3 >> undo >> return ()
    where
        step n = liftIO (putStrLn ("Do Step: " ++ show n))
                 `onUndo`
                 liftIO (putStrLn ("Undo Step: " ++ show n))

        tryAgain = liftIO (putStrLn "Will retry on undo")
                   `onUndo`
                   (retry >> liftIO (threadDelay 1000000 >> putStrLn "Retrying..."))

onUndo :: TransientIO a -> TransientIO a -> TransientIO a Source #

onBack for the default track; equivalent to onBack ().

undo :: TransIO a Source #

back for the default undo track; equivalent to back ().

retry :: TransIO () Source #

forward for the default undo track; equivalent to forward ().

undoCut :: TransientIO () Source #

backCut for the default track; equivalent to backCut ().

Finalization Primitives

Several finish handlers can be installed (using onFinish) that are called when the action is finalized using finish. All the handlers installed until the last initFinish are invoked in reverse order; thread boundaries do not matter. The following example prints "3" and then "2".

import Control.Monad.IO.Class (liftIO)
import Transient.Base (keep)
import Transient.Backtrack (initFinish, onFinish, finish)

main = keep $ do
        onFinish (\_ -> liftIO $ putStrLn "1")
        initFinish
        onFinish (\_ -> liftIO $ putStrLn "2")
        onFinish (\_ -> liftIO $ putStrLn "3")
        finish Nothing
        return ()

onFinish :: (Finish -> TransIO ()) -> TransIO () Source #

Clear all finish actions registered till now. initFinish= backCut (FinishReason Nothing)

Register an action that to be run when finish is called. onFinish can be used multiple times to register multiple actions. Actions are run in reverse order. Used in infix style.

onFinish' :: TransIO a -> (Finish -> TransIO a) -> TransIO a Source #

Run the action specified in the first parameter and register the second parameter as a finish action to be run when finish is called. Used in infix style.

noFinish :: TransIO () Source #

Abort finish. Stop executing more finish actions and resume normal execution. Used inside onFinish actions.

initFinish :: TransIO () Source #

Execute all the finalization actions registered up to the last initFinish, in reverse order. Either an exception or Nothing can be