monad-recorder-0.1.0: Record and replay the results of monadic actions

Copyright(c) 2017 Harendra Kumar
LicenseMIT-style
Maintainerharendra.kumar@gmail.com
Stabilityexperimental
PortabilityGHC
Safe HaskellNone
LanguageHaskell2010

Control.Monad.Trans.Recorder

Description

Results of the RecorderT computations are recorded in a running journal using the record combinator. A computation can be paused at any point using the pause primitive returning a Recording that can be used to restart the computation from the same point later. When the recording is replayed, the record combinator returns the previously recorded result of the computation from the journal instead of actually running the computation again.

import Control.Monad.IO.Class (liftIO)
import Control.Monad.Trans.Recorder (runRecorderT, record, pause, Paused(..), blank)
import Control.Exception (catch)

main = do
    recording <- (runRecorderT blank computation >> return blank) `catch` \(Paused r) -> return r
    putStrLn "Computation paused, resuming again with recorded logs"
    runRecorderT recording computation
    return ()

    where

    computation = do
         x1 <- record $ liftIO $ return 1
         record $ liftIO $ print ("A", x1)
         x2 <- record $ liftIO $ return 2
         record pause
         record $ liftIO $ print ("B", x1, x2)

Note that only those computations are replayed that are explicitly recorded. Unrecorded impure computations can result in the program misbehaving if it takes a different path upon replay. Instead of recording selectively you can enforce recording of each and every operation using the AutoRecorder module.

Synopsis

Documentation

data RecorderT m a Source #

The monad record and play transformer. Maintains a running log of the results of monadic actions.

Instances

MonadTrans RecorderT Source # 

Methods

lift :: Monad m => m a -> RecorderT m a #

MonadTransControl RecorderT Source # 

Associated Types

type StT (RecorderT :: (* -> *) -> * -> *) a :: * #

Methods

liftWith :: Monad m => (Run RecorderT -> m a) -> RecorderT m a #

restoreT :: Monad m => m (StT RecorderT a) -> RecorderT m a #

MonadBase b m => MonadBase b (RecorderT m) Source # 

Methods

liftBase :: b α -> RecorderT m α #

MonadBaseControl b m => MonadBaseControl b (RecorderT m) Source # 

Associated Types

type StM (RecorderT m :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (RecorderT m) b -> b a) -> RecorderT m a #

restoreM :: StM (RecorderT m) a -> RecorderT m a #

Monad m => Monad (RecorderT m) Source # 

Methods

(>>=) :: RecorderT m a -> (a -> RecorderT m b) -> RecorderT m b #

(>>) :: RecorderT m a -> RecorderT m b -> RecorderT m b #

return :: a -> RecorderT m a #

fail :: String -> RecorderT m a #

Functor m => Functor (RecorderT m) Source # 

Methods

fmap :: (a -> b) -> RecorderT m a -> RecorderT m b #

(<$) :: a -> RecorderT m b -> RecorderT m a #

Monad m => Applicative (RecorderT m) Source # 

Methods

pure :: a -> RecorderT m a #

(<*>) :: RecorderT m (a -> b) -> RecorderT m a -> RecorderT m b #

(*>) :: RecorderT m a -> RecorderT m b -> RecorderT m b #

(<*) :: RecorderT m a -> RecorderT m b -> RecorderT m a #

MonadIO m => MonadIO (RecorderT m) Source # 

Methods

liftIO :: IO a -> RecorderT m a #

MonadThrow m => MonadThrow (RecorderT m) Source # 

Methods

throwM :: Exception e => e -> RecorderT m a #

MonadCatch m => MonadCatch (RecorderT m) Source # 

Methods

catch :: Exception e => RecorderT m a -> (e -> RecorderT m a) -> RecorderT m a #

MonadMask m => MonadMask (RecorderT m) Source # 

Methods

mask :: ((forall a. RecorderT m a -> RecorderT m a) -> RecorderT m b) -> RecorderT m b #

uninterruptibleMask :: ((forall a. RecorderT m a -> RecorderT m a) -> RecorderT m b) -> RecorderT m b #

Monad m => MonadRecorder (RecorderT m) Source # 
type StT RecorderT a Source # 
type StM (RecorderT m) a Source # 
type StM (RecorderT m) a = ComposeSt RecorderT m a

data Journal Source #

The internal log state kept when recording or replaying.

class Monad m => MonadRecorder m where Source #

A monad with the ability to record and play the results of monadic actions.

Minimal complete definition

getJournal, putJournal, play

Methods

getJournal :: m Journal Source #

Retrieve the record and replay journal. Used by the implementation of record and play.

putJournal :: Journal -> m () Source #

Replace the record and replay journal. Used by the implementation of record and play.

play :: Recording -> m () Source #

Play a previously recorded journal. This function can be used to set a replay journal at any point.

runRecorderT :: Monad m => Recording -> RecorderT m a -> m a Source #

Run a fresh RecorderT computation using blank recording or resume a paused computation using captured recording. The captured state of the action is restored and the action resumes right after the pause call that paused the action.

class Recordable a where Source #

A type that can be recorded.

Minimal complete definition

toJournal, fromJournal

Instances

(Show a, Read a) => Recordable a Source # 

data Recording Source #

The log entries returned when an action is suspended.

record :: (Recordable a, Read a, Show a, MonadRecorder m) => m a -> m a Source #

Add the result of an action to the recording journal. During replay, if the result of an action is available in the replay journal then get it from the journal instead of running the action.

pause :: (MonadRecorder m, MonadThrow m) => m () Source #

Pause a computation before completion for resuming later. Throws Paused exception which carries the current recorded logs.