monad-recorder-0.1.1: 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.AutoRecorder

Description

Unlike RecorderT which records selective operations using the record combinator AutoRecorderT monad enforces recording of all operations in the monad. This ensures that we do not miss recording any monadic operation that could cause problems on replay.

import Control.Monad.IO.Class (liftIO)
import Control.Monad.Trans.Recorder (runRecorderT, record, pause, Paused(..), blank)
import Control.Monad.Trans.AutoRecorder (recorder, AutoRecorderT(R))
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 = recorder $ do
         x1 <- R $ liftIO $ return 1
         R $ liftIO $ print ("A", x1)
         x2 <- R $ liftIO $ return 2
         R pause
         R $ liftIO $ print ("B", x1, x2)

Synopsis

Documentation

data AutoRecorderT m a where Source #

A monad that enforces recording of the results of all monadic actions. The constructor R lifts a MonadRecorder monad to AutoRecorderT.

Constructors

R :: (MonadRecorder m, Show a, Read a) => m a -> AutoRecorderT m a 

Instances

Monad (AutoRecorderT m) Source # 

Methods

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

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

return :: a -> AutoRecorderT m a #

fail :: String -> AutoRecorderT m a #

Functor (AutoRecorderT f) Source # 

Methods

fmap :: (a -> b) -> AutoRecorderT f a -> AutoRecorderT f b #

(<$) :: a -> AutoRecorderT f b -> AutoRecorderT f a #

Applicative (AutoRecorderT f) Source # 

Methods

pure :: a -> AutoRecorderT f a #

(<*>) :: AutoRecorderT f (a -> b) -> AutoRecorderT f a -> AutoRecorderT f b #

liftA2 :: (a -> b -> c) -> AutoRecorderT f a -> AutoRecorderT f b -> AutoRecorderT f c #

(*>) :: AutoRecorderT f a -> AutoRecorderT f b -> AutoRecorderT f b #

(<*) :: AutoRecorderT f a -> AutoRecorderT f b -> AutoRecorderT f a #

recorder :: (MonadRecorder m, MonadThrow m, Show a, Read a) => AutoRecorderT m a -> m a Source #

Run the AutoRecorderT monad recording all operations in it.