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

Control.Monad.Trans.Tardis

Description

The data definition of a TardisT as well as its primitive operations, and straightforward combinators based on the primitives.

See Control.Monad.Tardis for the general explanation of what a Tardis is and how to use it.

Synopsis

The Tardis monad transformer

newtype 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.

Constructors

TardisT 

Fields

  • runTardisT :: (bw, fw) -> m (a, (bw, fw))

    A TardisT is merely an effectful state transformation

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 #

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.

The Tardis monad

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.

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

A Tardis is merely a pure state transformation.

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).

Primitive Tardis operations

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

From a stateful computation, construct a Tardis. This is the pure parallel to the constructor TardisT, and is polymorphic in the transformed monad.

getPast :: Monad m => TardisT bw fw m fw Source #

Retrieve the current value of the 'forwards-traveling' state, which therefore came forwards from the past. You can think of forwards-traveling state as traveling downwards through your code.

getFuture :: Monad m => TardisT bw fw m bw Source #

Retrieve the current value of the 'backwards-traveling' state, which therefore came backwards from the future. You can think of backwards-traveling state as traveling upwards through your code.

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

Set the current value of the 'backwards-traveling' state, which will therefore be sent backwards to the past. This value can be retrieved by calls to "getFuture" located above the current location, unless it is overwritten by an intervening "sendPast".

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

Set the current value of the 'forwards-traveling' state, which will therefore be sent forwards to the future. This value can be retrieved by calls to "getPast" located below the current location, unless it is overwritten by an intervening "sendFuture".

Composite Tardis operations

modifyForwards :: MonadFix m => (fw -> fw) -> TardisT bw fw m () Source #

Modify the forwards-traveling state as it passes through from past to future.

modifyBackwards :: MonadFix m => (bw -> bw) -> TardisT bw fw m () Source #

Modify the backwards-traveling state as it passes through from future to past.

getsPast :: MonadFix m => (fw -> a) -> TardisT bw fw m a Source #

Retrieve a specific view of the forwards-traveling state.

getsFuture :: MonadFix m => (bw -> a) -> TardisT bw fw m a Source #

Retrieve a specific view of the backwards-traveling state.

Other

mapTardisT :: (m (a, (bw, fw)) -> n (b, (bw, fw))) -> TardisT bw fw m a -> TardisT bw fw n b Source #

A function that operates on the internal representation of a Tardis can also be used on a Tardis.

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)