Safe Haskell | None |
---|
This module provides facilities for building IO
actions in such a way that, if one IO
action in a sequence
throws an exception, the effects of previous actions will be undone.
Here's an example of how to use this module. Suppose you have two files that, every so often, must be updated
from some external data source. The new contents for a particular file are retrieved from the external data
source via a function getNewContents ::
. FilePath
-> IO
String
getNewContents
could throw an exception, as
could any of the other IO
actions that we invoke, and if an exception is thrown while the files are being updated,
we want all changes made so far to either of the files to be rolled back. Using this module, we could do this thus:
import Control.MonadTransaction import System.IO import System.FilePath.Posix getNewContents :: FilePath -> IO String getNewContents path = ... updateFile :: FilePath -> UndoableIO () updateFile path = do -- get current contents oldContents <- doAction $ readFile path -- get new contents from external data source newContents <- doAction $ getNewContents path -- write new contents doAction $ writeFile path newContents -- add an undo action that rewrites the old contents addUndoer $ writeFile path oldContents main :: IO () main = exec $ do updateFile "file1" updateFile "file2"
In this code, we use the following from this module: the UndoableIO
monad, and the functions doAction
, addUndoer
,
and exec
. The UndoableIO
monad is like a context for combining IO
actions together into a transaction. Inside
UndoableIO
, we invoke IO
actions using the function doAction
. When executed, these actions will be sequenced as they would
be if they had been combined as usual inside the IO
monad. When we invoke an IO
action whose effect should be undone if an
exception occurs later, we add an "undoer" --- that is, an IO
action that undoes the effect --- using the function
addUndoer
. UndoableIO
maintains a stack of undoers, and if an exception occurs during execution, the undoers will
be executed in the reverse of the order in which they were added, and then the exception will be rethrown.
So, in updateFile
we use doAction
to call IO
actions that read from and write to the files and retrieve strings from the
external data source, and at the end we add an undoer that restores the original contents. In main
, we combine the UndoableIO
actions returned by two calls to updateFile
into one. We pass the resulting UndoableIO
action to exec
, which
converts it into an IO
action. If an exception occurs when this IO
action is executed, then any changes so far made to the
files will be undone using the undoers added by updateFile
.
- type UndoableIO a = UndoableM IO a
- doAction :: IO a -> UndoableIO a
- addUndoer :: IO () -> UndoableIO ()
- exec :: UndoableIO a -> IO a
- rollback :: UndoableIO ()
- makeUndoable :: IO a -> IO () -> UndoableIO a
- data ManualUndo = ManualUndo
- data UndoableM m a = Do (m (a, m ()))
- class Monad m => ExceptionalMonad m where
- doActionM :: ExceptionalMonad m => m a -> UndoableM m a
- addUndoerM :: ExceptionalMonad m => m () -> UndoableM m ()
- execM :: Monad m => UndoableM m a -> m a
- rollbackM :: ExceptionalMonad m => UndoableM m ()
- makeUndoableM :: ExceptionalMonad m => m a -> m () -> UndoableM m a
IO Transactions
type UndoableIO a = UndoableM IO aSource
An "undoable action" is a wrapper for an IO
action (the "doer") that combines it with another
IO
action (the "undoer") that undoes the effects of the first one.
Undoable actions are monads, and when sequenced together they act like transactions involving IO
operations.
As undoable actions are sequenced together, their doers are also sequenced together and their undoers
are placed into a stack. When the doers are executed, if one of them throws an exception, the undoers
so far added to the stack are executed in reverse the reverse of the order in which they were added to the stack,
and then the exception is rethrown; no other doers (or undoers) are executed. If no exception is thrown, none of
the undoers are executed.
:: IO a | The "doer": the action to perform. |
-> UndoableIO a |
Make an undoable action without any undoer.
This undoable action will not add any undoer to the undoer stack.
:: IO () | An "undoer": an action that will be added to the undoer stack. |
-> UndoableIO () |
Add an undoer to the undoer stack.
exec :: UndoableIO a -> IO aSource
Convert an UndoableIO
action into an IO
action that invokes
the actions (and the undoers if necessary) that were added to the
UndoableIO
action.
rollback :: UndoableIO ()Source
Stop execution, run the actions on the undoer stack, and throw ManualUndo
.
:: IO a | The "doer": the action to perform. |
-> IO () | An "undoer": an action that undoes the effect of the other one. |
-> UndoableIO a |
Make an undoable action.
Internal Stuff
A monad for combining other, side-effectual monads in a transaction
that can be rolled back if an exception is thrown. m
must implement
ExceptionalMonad
.
This type is for implementing transactions and should not be used directly by code that uses transactions.
Do (m (a, m ())) |
ExceptionalMonad m => Monad (UndoableM m) |
class Monad m => ExceptionalMonad m whereSource
An ExceptionalMonad
is a monad that in which Exception
s can be thrown and caught.
A monad m
must implement ExceptionalMonad
in order to work with UndoableM
.
doActionM :: ExceptionalMonad m => m a -> UndoableM m aSource
addUndoerM :: ExceptionalMonad m => m () -> UndoableM m ()Source
rollbackM :: ExceptionalMonad m => UndoableM m ()Source
makeUndoableM :: ExceptionalMonad m => m a -> m () -> UndoableM m aSource