tardis-0.4.3.0: Bidirectional state monad transformer
Safe HaskellSafe-Inferred
LanguageHaskell2010

Control.Monad.Tardis

Description

This module re-exports both MonadTardis and TardisT (Wherever there is overlap, the MonadTardis version is preferred.)

The recommended usage of a Tardis is to import this module.

Synopsis

Re-exports

type Tardis bw fw = TardisT bw fw Identity Source #

Using a Tardis with no monad underneath will prove to be most common use case. Practical uses of a TardisT require that the underlying monad be an instance of MonadFix, but note that the IO instance of MonadFix is almost certainly unsuitable for use with Tardis code.

data TardisT bw fw m a Source #

A TardisT is parameterized by two state streams: a 'backwards-traveling' state and a 'forwards-traveling' state. This library consistently puts the backwards-traveling state first whenever the two are seen together.

Instances

Instances details
MonadFix m => MonadTardis bw fw (TardisT bw fw m) Source # 
Instance details

Defined in Control.Monad.Tardis.Class

Methods

getPast :: TardisT bw fw m fw Source #

getFuture :: TardisT bw fw m bw Source #

sendPast :: bw -> TardisT bw fw m () Source #

sendFuture :: fw -> TardisT bw fw m () Source #

tardis :: ((bw, fw) -> (a, (bw, fw))) -> TardisT bw fw m a Source #

MFunctor (TardisT bw fw :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Control.Monad.Trans.Tardis

Methods

hoist :: forall m n (b :: k). Monad m => (forall a. m a -> n a) -> TardisT bw fw m b -> TardisT bw fw n b #

MonadTrans (TardisT bw fw) Source # 
Instance details

Defined in Control.Monad.Trans.Tardis

Methods

lift :: Monad m => m a -> TardisT bw fw m a #

MonadFix m => Monad (TardisT bw fw m) Source # 
Instance details

Defined in Control.Monad.Trans.Tardis

Methods

(>>=) :: TardisT bw fw m a -> (a -> TardisT bw fw m b) -> TardisT bw fw m b #

(>>) :: TardisT bw fw m a -> TardisT bw fw m b -> TardisT bw fw m b #

return :: a -> TardisT bw fw m a #

MonadFix m => Functor (TardisT bw fw m) Source # 
Instance details

Defined in Control.Monad.Trans.Tardis

Methods

fmap :: (a -> b) -> TardisT bw fw m a -> TardisT bw fw m b #

(<$) :: a -> TardisT bw fw m b -> TardisT bw fw m a #

MonadFix m => MonadFix (TardisT bw fw m) Source # 
Instance details

Defined in Control.Monad.Trans.Tardis

Methods

mfix :: (a -> TardisT bw fw m a) -> TardisT bw fw m a #

MonadFix m => Applicative (TardisT bw fw m) Source # 
Instance details

Defined in Control.Monad.Trans.Tardis

Methods

pure :: a -> TardisT bw fw m a #

(<*>) :: TardisT bw fw m (a -> b) -> TardisT bw fw m a -> TardisT bw fw m b #

liftA2 :: (a -> b -> c) -> TardisT bw fw m a -> TardisT bw fw m b -> TardisT bw fw m c #

(*>) :: TardisT bw fw m a -> TardisT bw fw m b -> TardisT bw fw m b #

(<*) :: TardisT bw fw m a -> TardisT bw fw m b -> TardisT bw fw m a #

runTardis :: Tardis bw fw a -> (bw, fw) -> (a, (bw, fw)) Source #

A Tardis is merely a pure state transformation.

evalTardisT :: Monad m => TardisT bw fw m a -> (bw, fw) -> m a Source #

Run a Tardis, and discard the final state, observing only the resultant value.

execTardisT :: Monad m => TardisT bw fw m a -> (bw, fw) -> m (bw, fw) Source #

Run a Tardis, and discard the resultant value, observing only the final state (of both streams). Note that the final state of the backwards-traveling state is the state it reaches by traveling from the bottom of your code to the top.

evalTardis :: Tardis bw fw a -> (bw, fw) -> a Source #

Run a Tardis, and discard the final state, observing only the resultant value.

execTardis :: Tardis bw fw a -> (bw, fw) -> (bw, fw) Source #

Run a Tardis, and discard the resultant value, observing only the final state (of both streams).

noState :: (a, b) Source #

Some Tardises never observe the initial state of either state stream, so it is convenient to simply hand dummy values to such Tardises.

noState = (undefined, undefined)

What is a Tardis?

A Tardis is the combination of the State monad transformer and the Reverse State monad transformer.

The State monad transformer features a forwards-traveling state. You can retrieve the current value of the state, and you can set its value, affecting any future attempts to retrieve it.

The Reverse State monad transformer is just the opposite: it features a backwards-traveling state. You can retrieve the current value of the state, and you can set its value, affecting any past attempts to retrieve it. This is a bit weirder than its forwards-traveling counterpart, so its Monad instance additionally requires that the underlying Monad it transforms must be an instance of MonadFix.

A Tardis is nothing more than mashing these two things together. A Tardis gives you two states: one which travels backwards (or upwards) through your code (referred to as bw), and one which travels forwards (or downwards) through your code (referred to as fw). You can retrieve the current value of either state, and you can set the value of either state. Setting the forwards-traveling state will affect the future, while setting the backwards-traveling state will affect the past. Take a look at how Monadic bind is implemented for TardisT:

m >>= f  = TardisT $ \ ~(bw, fw) -> do
  rec (x,  ~(bw'', fw' )) <- runTardisT m (bw', fw)
      (x', ~(bw' , fw'')) <- runTardisT (f x) (bw, fw')
  return (x', (bw'', fw''))

Like the Reverse State monad transformer, TardisT's Monad instance requires that the monad it transforms is an instance of MonadFix, as is evidenced by the use of rec. Notice how the forwards-traveling state travels normally: first it is fed to m, producing fw', and then it is fed to f x, producing fw''. The backwards-traveling state travels in the opposite direction: first it is fed to f x, producing bw', and then it is fed to m, producing bw''.

How do you use a Tardis?

A Tardis provides four primitive operations, corresponding to the get and put for each of its two states. The most concise way to explain it is this: getPast retrieves the value from the latest sendFuture, while getFuture retrieves the value from the next sendPast. Beware the pitfall of performing send and get in the wrong order. Let's consider forwards-traveling state:

do sendFuture "foo"
   x <- getPast

In this code snippet, x will be "foo", because getPast grabs the value from the latest sendFuture. If you wanted to observe that state before overwriting it with "foo", then re-arrange the code so that getPast happens earlier than sendFuture. Now let's consider backwards-traveling state:

do x <- getFuture
   sendPast "bar"

In this code snippet, x will be "bar", because getFuture grabs the value from the next sendPast. If you wanted to observe that state before overwriting it with "bar", then re-arrange the code so that getFuture happens later than sendPast.

TardisT is an instance of MonadFix. This is especially important when attempting to write backwards-traveling code, because the name binding occurs later than its usage. The result of the following code will be (11, "Dan Burton").

flip execTardis (10, "Dan") $ do
  name <- getPast
  sendFuture (name ++ " Burton")
  rec
    sendPast (score + 1)
    score <- getFuture
  return ()

To avoid using rec, you may find modifyBackwards to be useful. This code is equivalent to the previous example:

flip execTardis (10, "Dan") $ do
  modifyForwards (++ " Burton")
  modifyBackwards (+ 1)