Swap inner and outer monads - haskell

How to convert StateT g (Either E) T to ExceptT E (StateT g Identity) T?
Probably, some mix of traverse and hoist could be useful here.

You can't exchange an arbitrary pair of monads. But you can exchange these two particular monads. It's easiest to understand if you expand the newtypes in the definitions of those monad transformers.
Given
newtype StateT s m a = StateT { runStateT :: s -> m (s, a) }
and
newtype ExceptT e m a = ExceptT { runExceptT :: m (Either e a) }
expanding the newtypes in your first type expression gives us the isomorphism
StateT s (Either e) a <-> s -> Either e (s, a)
whereas for the second we get
ExceptT e (StateT s Identity) a <-> s -> (s, Either e a)
Note that Either e (s, a) may or may not contain an s, whereas (s, Either e a) always does. Now, one can go from the latter to the former just by traverseing the tuple inside the function, but going the other way requires some domain-specific reasoning: if the computation throws an error then we should plumb the state through unchanged to the catcher of the error. (Is this the right thing to do? I find it rather debatable.)
stateTEitherToExceptTState :: (s -> Either e (s, a)) -> (s -> (s, Either e a))
stateTEitherToExceptTState f s =
case f s of
Left e -> (s, Left e)
Right sa -> fmap Right sa

Related

Lifting a complete monadic action to a transformer (>>= but for Monad Transformers)

I looked hard to see if this may be a duplicate question but couldn't find anything that addressed specifically this. My apologies if there actually is something.
So, I get how lift works, it lifts a monadic action (fully defined) from the outer-most transformer into the transformed monad. Cool.
But what if I want to apply a (>>=) from one level under the transformer into the transformer? I'll explain with an example.
Say MyTrans is a MonadTrans, and there is also an instance Monad m => Monad (MyTrans m). Now, the (>>=) from this instance will have this signature:
instance Monad m => Monad (MyTrans m) where
(>>=) :: MyTrans m a -> (a -> MyTrans m b) -> MyTrans m b
but what I need is something like this:
(>>=!) :: Monad m => MyTrans m a -> (m a -> MyTrans m b) -> MyTrans m b
In general:
(>>=!) :: (MonadTrans t, Monad m) => t m a -> (m a -> t m b) -> t m b
It looks like a combination of the original (>>=) and lift, except it really isn't. lift can only be used on covariant arguments of type m a to transform them into a t m a, not the other way around. In other words, the following has the wrong type:
(>>=!?) :: Monad m => MyTrans m a -> (a -> m b) -> MyTrans m b
x >>=!? f = x >>= (lift . f)
Of course a general colift :: (MonadTrans t, Monad m) => t m a -> m a makes absolutely zero sense, because surely the transformer is doing something that we cannot just throw away like that in all cases.
But just like (>>=) introduces contravariant arguments into the monad by ensuring that they will always "come back", I thought something along the lines of the (>>=!) function would make sense: Yes, it in some way makes an m a from a t m a, but only because it does all of this within t, just like (>>=) makes an a from an m a in some way.
I've thought about it and I don't think (>>=!) can be in general defined from the available tools. In some sense it is more than what MonadTrans gives. I haven't found any related type classes that offer this either. MFunctor is related but it is a different thing, for changing the inner monad, but not for chaining exclusively transformer-related actions.
By the way, here is an example of why you would want to do this:
EDIT: I tried to present a simple example but I realized that that one could be solved with the regular (>>=) from the transformer. My real example (I think) cannot be solved with this. If you think every case can be solved with the usual (>>=), please do explain how.
Should I just define my own type class for this and give some basic implementations? (I'm interested in StateT, and I'm almost certain it can be implemented for it) Am I doing something in a twisted way? Is there something I overlooked?
Thanks.
EDIT: The answer provided by Fyodor matches the types, but does not do what I want, since by using pure, it is ignoring the monadic effects of the m monad. Here is an example of it giving the wrong answer:
Take t = StateT Int and m = [].
x1 :: StateT Int [] Int
x1 = StateT (\s -> [(1,s),(2,s),(3,s)])
x2 :: StateT Int [] Int
x2 = StateT (\s -> [(1,s),(2,s),(3,s),(4,s))])
f :: [Int] -> StateT Int [] Int
f l = StateT (\s -> if (even s) then [] else (if (even (length l)) then (fmap (\z -> (z,z+s)) l) else [(123,123)]))
runStateT (x1 >>= (\a -> f (pure a))) 1 returns [(123,123),(123,123),(123,123)] as expected, since both 1 is odd and the list in x1 has odd length.
But runStateT (x2 >>= (\a -> f (pure a))) 1 returns [(123,123),(123,123),(123,123),(123,123)], whereas I would have expected it to return [(1,2),(2,3),(3,4),(4,5)], since the 1 is odd and the length of the list is even. Instead, the evaluation of f is happening on the lists [(1,1)], [(2,1)], [(3,1)] and [(4,1)] independently, due to the pure call.
This can be very trivially implemented via bind + pure. Consider the signature:
(>>=!) :: (Monad m, MonadTrans t) => t m a -> (m a -> t m a) -> t m a
If you use bind on the first argument, you get yourself a naked a, and since m is a Monad, you can trivially turn that naked a into an m a via pure. Therefore, the straightforward implementation would be:
(>>=!) x f = x >>= \a -> f (pure a)
And because of this, bind is always strictly more powerful than your proposed new operation (>>=!), which is probably the reason it doesn't exist in the standard libraries.
I think it may be possible to propose more clever interpretations of (>>=!) for some specific transformers or specific underlying monads. For example, if m ~ [], one might imagine passing the whole list as m a instead of its elements one by one, as my generic implementation above would do. But this sort of thing seems too specific to be implemented in general.
If you have a very specific example of what you're after, and you can show that my above general implementation doesn't work, then perhaps I can provide a better answer.
Ok, to address your actual problem from the comments:
I have a function f :: m a -> m b -> m c that I want to transform into a function ff :: StateT s m a -> StateT s m b -> StateT s m c
I think looking at this example may illustrate the difficulty better. Consider the required signature:
liftish :: Monad m => (m a -> m b -> m c) -> StateT m a -> StateT m b -> StateT m c
Presumably, you'd want to keep the effects of m that are already "imprinted" within the StateT m a and StateT m b parameters (because if you don't - my simple solution above will work). To do this, you can "unwrap" the StateT via runStateT, which will get you m a and m b respectively, which you can then use to obtain m c:
liftish f sa sb = do
s <- get
let ma = fst <$> runStateT sa s
mb = fst <$> runStateT sb s
lift $ f ma mb
But here's the trouble: see those fst <$> in there? They are throwing away the resulting state. The call to runStateT sa s results not only in the m a value, but also in the new, modified state. And same goes for runStateT sb s. And presumably you'd want to get the state that resulted from runStateT sa and pass it to runStateT sb, right? Otherwise you're effectively dropping some state mutations.
But you can't get to the resulting state of runStateT sa, because it's "wrapped" inside m. Because runStateT returns m (a, s) instead of (m a, s). If you knew how to "unwrap" m, you'd be fine, but you don't. So the only way to get that intermediate state is to run the effects of m:
liftish f sa sb = do
s <- get
(c, s'') <- lift $ do
let ma = runStateT sa s
(_, s') <- ma
let mb = runStateT sb s'
(_, s'') <- mb
c <- f (fst <$> ma) (fst <$> mb)
pure (c, s'')
put s''
pure c
But now see what happens: I'm using ma and mb twice: once to get the new states out of them, and second time by passing them to f. This may lead to double-running effects or worse.
This problem of "double execution" will, I think, show up for any monad transformer, simply because the transformer's effects are always wrapped inside the underlying monad, so you have a choice: either drop the transformer's effects or execute the underlying monad's effects twice.
I think what you "really want" is
(>>>==) :: MyTrans m a -> (forall b. m b -> MyTrans n b) -> MyTrans n a
-- (=<<) = flip (>>=) is nicer to think about, because it shows that it's a form of function application
-- so let's think about
(==<<<) :: (forall a. m b -> MyTrans n b) -> (forall a. MyTrans m a -> MyTrans n a)
-- hmm...
type (~>) a b = forall x. a x -> b x
(==<<<) :: (m ~> MyTrans n) -> MyTrans m ~> MyTrans n
-- look familiar?
That is, you are describing monads on the category of monads.
class MonadTrans t => MonadMonad t where
-- returnM :: m ~> t m
-- but that's just lift, therefore the MonadTrans t superclass
-- note: input must be a monad homomorphism or else all bets are off
-- output is also a monad homomorphism
(==<<<) :: (Monad m, Monad n) => (m ~> t n) -> t m ~> t n
instance MonadMonad (StateT s) where
-- fairly sure this is lawful
-- EDIT: probably not
f ==<<< StateT x = do
(x, s) <- f <$> x <$> get
x <$ put s
However, making your example work is just not going to happen. It is too unnatural. StateT Int [] is the monad for programs that nondeterministically evolve the state. It is an important property of that monad that each "parallel universe" receives no communication from the others. The specific operation you are performing will probably not be provided by any useful typeclass. You can only do part of it:
f :: [] ~> StateT Int []
f l = StateT \s -> if odd s && even (length l) then fmap (\x -> (x, s)) l else []
f ==<<< x1 = []
f ==<<< x2 = [(1,1),(2,1),(3,1),(4,1)]

Function in Haskell to map over a MonadTrans?

I have recently decided to start using monad transformations instead of stacking my monads, since it seems it's the right thing to do. I wasn't really stacking many monads before anyway. I get (I think) the idea behind it and the lift function, that, as I understand it, acts as a sort of return for the transformation (puts something from the underlying monad into the transformed monad).
So far so good, but I don't see anything similar to an fmap function for monad transformations. Let me give you an example. Say I have a custom monad, m, and I use a StateT transformation on it, therefore using the type StateT s m a instead of m (State s a).
Now, it so happens that in my monad m, I have a function that transforms the monadic element (in fact it is one of the constructors of the monad, if you need details I can give) while keeping in some sense the underlying values: myFunc :: m a -> m a.
So I'm building a recursive function recFunc :: State s a -> [t] -> m (State s a) that looks similar to something like this:
recFunc :: State s a -> [t] -> m (State s a)
recFunc x [] = return x
recFunc x (t:ts) = myFunc (recFunc x ts)
But if I try to replicate this using monad transformations, I run into problems because I can find no way to plug in myFunc into the mix. It does not matter whether you write the input as State s a or as StateT s Identity a (which would be algebraically more precise?)
recFuncT :: StateT s Identity a -> [t] -> StateT s m a
recFuncT x [] = ???
recFuncT x (t:ts) = ????? where rec = recFuncT x ts
So what I'm looking for is something like the (invented, and don't know how I would implement, if possible) following functions:
transmap :: (MonadTrans t, Monad m) => (forall b. m b -> m b) -> t m a -> t m a
transmap = ???
transreturn :: (MonadTrans t, Monad m) => m (t Identity a) -> t m a
transreturn = ???
I have the feeling I should be able to define these using lift, but I don't see how, to be honest.
If I had them, then I could do this:
recFuncT :: StateT s Identity a -> [t] -> StateT s m a
recFuncT x [] = transreturn (return x)
recFuncT x (t:ts) = transmap myFunc (recFuncT x ts)
Maybe what I really want is something more basic. I want the assumed isomorphism between t m a and m (t Identity a) to be explicit, so I'm looking for functions:
fromTrans :: t m a -> m (t Identity a)
toTrans :: m (t Identity a) -> t m a
As far as I understand monad transformers, these functions should always exist and be fairly straightforward, right?
With these I could obviously implement transmap and transreturn:
transmap :: (MonadTrans t, Monad m) => (forall b. m b -> m b) -> t m a -> t m a
transmap f x = toTrans (f (fromTrans x))
transreturn :: (MonadTrans t, Monad m) => m (t Identity a) -> t m a
transreturn = toTrans
I am sure there is something obvious that I am overlooking. Please point at it for me.
Thanks.
It appears that one concept you're seeking can be found in the mmorph package:
class MFunctor t where
-- The argument is generally required to be a monad morphism,
-- but some instances will work sensibly when it's not.
hoist :: Monad m => (forall x. m x -> n x) -> t m a -> t n a
This is a little more general than your version because it allows the underlying monad to be replaced.
From the discussion in the comments, it sounds like what you really want is a monad transformer for your custom monad that is then applied to the base monad State. In other words, to the extent that your custom monad is "nearly" a list:
newtype Listish a = Listish [a]
its transformer version would have type:
newtype ListishT m a = ListishT [m a]
and so your final monad transformer stack would be:
type M s = ListishT (State s)
which is isomorphic to your monad stack
[State s a] AKA Listish (State s a)
Be sure not to over-generalize the pattern for creating a transformer from an underlying monad, however. While transformers for some monads:
newtype List a = List [a]
newtype Reader r a = Reader (r -> a)
are sensibly derived by replacing "a" with "m a":
newtype ListT m a = ListT [m a]
newtype ReaderT r m a = ReaderT (r -> m a)
transformers for other types are derived differently. For example:
newtype State s a = State (s -> (a, s))
newtype Writer w a = Writer (a, w)
give:
newtype StateT s a = StateT (s -> m (a, s))
-- **NOT** StateT (s -> (m a, s))
newtype WriterT s a = WriterT (m (a, w))
-- **NOT** WriterT (m a, w)
In particular, there is no monad transformer for IO, because the simple substitution
newtype BadIOT m a = BadIOT (IO (m a))
is, as you point out, silly.
EDIT: All of the below makes no sense. I leave it strikedthrough. Good answer below.
For the record, my final solution was neither to use or implement a monad transformer, and instead simply implement the following function: (my custom monad is called EnumProc):
(..>>=) :: Monad m => EnumProc (m a) -> (a -> m b) -> EnumProc (m b)
en ..>>= f = en <$> (>>= f)
infixl 7 ..>>=
This allows me to deal with monadic computations inside my monad while keeping the outside monad structure. I was surprised myself when an fmap sufficed.
I then use EnumProc (State s a) as type throughout.
After a while, I finally came up with exactly what I was looking for since the beginning. I can use StateT exactly the way I wanted, and it has exactly the semantics I thought it had, but I did not explain it well (and put mistakes in what I wrote).
Going back to my original post, I need not have a State as input, the State/StateT monad already includes the input in the monadic element. So what I needed was a function recFuncT :: [t] -> StateT s m a that behaved equivalently to the following non-transformer one:
recFunc :: a -> [t] -> m (State s a)
recFunc x [] = return (return x)
recFunc x (t:ts) = myFunc (recFunc x ts)
It can be implemented directly, using the constructor StateT and runStateT. Here it is:
recFuncT :: a -> [t] -> StateT m s a
recFuncT x [] = return x
recFuncT x (t:ts) = StateT (\s -> myFunc (runStateT (recFuncT x ts) s))
Moreover, the function transmap can also be implemented in general, at least for StateT:
transmap :: Monad m => (forall b. m b -> m b) -> StateT s m a -> StateT s m a
transmap f st = StateT (\s -> f (runStateT st s)
And then we could write recFuncT nicely in terms of it:
recFuncT :: a -> [t] -> StateT m s a
recFuncT x [] = return x
recFuncT x (t:ts) = transmap myFunc (recFuncT x ts)
I realize this does not really match with the code that I included originally, but it does match with the overall principle I was trying to appeal to saying that the StateT transformer is like adding state to my monad m, and therefore anything that can be done at the m (State s a) level can be done at the StateT s m a level.

Monad Transformer: troubles defining bind due to different monads

I have a Monad of named TaskMonad, defined as follows:
data TaskMonad a = TaskMonad (Environment -> (TaskResult a, Environment))
where Environment is a record type and TaskResult is an ADT; but they are not important for the problem.
I have defed Functor, Applicative and Monad instances for TaskMonad, and I now want to be able to combine this monad with other Monads (e.g. IO), So I defined a new type as follows:
newtype Task m a = Task { runTask :: m (TaskMonad a) }
I have defined Functor and Applicative as follows:
instance Monad m => Functor (Task m) where
fmap f ta = Task $ do tma <- runTask ta
return (fmap f tma)
instance Monad m => Applicative (Task m) where
pure = Task . return . return
(<*>) prod tx = Task $ do tmprod <- runTask prod
tmtx <- runTask tx
return (tmprod <*> tmtx)
And I also made Task member of the MonadTrans class:
instance MonadTrans Task where
lift = Task . (liftM return)
So far so good (or atleast it compiles..), but now I want to define the instance for Monad, but I am running into problems here:
instance Monad m => Monad (Task m) where
return = pure
(>>=) ta tb = ...
I attempted multiple things, most attempts starting out like this:
(>>=) ta tb = Task $ do tma <- runTask ta
Now we have tma :: TaskMonad a inside the do block for the m monad. Now what I would like to do, is somehow calling the >>= instance for TaskMonad so I can get the result of tma, a value of type a so I can parameterize tb with it to obtain a value of Task b. But I am within the context of the m monad and I'm running into all kinds of problems.
How could I obtain tma's result to provide it to tb?
Okay, I don't know how much this helps, but if you actually start with a transformer from day 0 (in TaskMonad), the way you can do it is:
data TaskMonad m a = TaskMonad (Environment -> m (TaskResult a, Environment)) deriving Functor
instance Monad m => Monad (TaskMonad m) where
return = pure
(TaskMonad f) >>= b = TaskMonad $ \e -> do
(TaskResult r, e') <- f e
let (TaskMonad g) = b r
g e'
instance (Monad m, Functor m) => Applicative (TaskMonad m) where
pure a = TaskMonad $ \e -> return (TaskResult a, e)
(TaskMonad f) <*> (TaskMonad g) = TaskMonad $ \e -> do
(TaskResult f', e') <- f e
(TaskResult a, e'') <- g e'
return (TaskResult (f' a), e'')
Probably there's also a way to do that the way you originally intended, but I am pretty sure original Task would also need to be changed to take initial Environment.
I presume you're actually doing more than State in your monad, so that would need to be put in respective instances, but I think the framework for that should help.
And of course, shall you ever need to use a non-transformer version, just pass in Identity for m.
Disclaimer:
I know this implemenation of Applicative instance doesn't make sense, but I was building that on old GHC w/o ApplicativeDo and it was literally the easiest thing to put the silly constraint there.
As described in #BartekBanachewicz's answer, putting the monad m inside -> is the way to go.
I believe it's not possible to do it the way you want by having m (TaskMonad a), at least not generically. In general monads aren't closed under composition and this is an example of such a situation.
Let me give a simplified example (some theory will be required for it): Let's work with the reader monad instead of the state monad, let's drop TaskResult and let's have the environment as a type parameter. So TaskMonad will be just m (r -> a). Now let's assume it's a monad, then there is
join :: m (r -> (m (r -> a))) -> m (r -> a)
Specializing a to Void (see also Bottom type) and m to Either r we get
join :: Either r (r -> (Either r (r -> Void))) -> Either r (r -> Void)
But then we're able to construct
doubleNegationElimination :: Either r (r -> Void)
doubleNegationElimination = join (Right Left)
as Right Left :: Either r (r -> Either r (r -> Void)). Through Curry-Howard isomorphism this would mean that we'd be able to prove Double negation elimination
in intuitionistic logic, which is a contradiction.
Your situation is somewhat more complex, but a similar argument could be made there too. The only hole there is that we assumed that the "environment" part, r, was generic, so won't work if your join or >>= is somehow specific for Environment. So you might be able to do it in such a case, but my guess is you'll then encounter other problems preventing you to get a proper non-trivial Monad instance.

Unnecessary assignment in do sequence

Let's look at:
instance (Error e) => MonadTrans (ErrorT e) where
lift m = ErrorT $ do
a <- m
return (Right a)
I cannot understand why is necessary a <- m. Why we don't write just:
instance (Error e) => MonadTrans (ErrorT e) where
lift m = ErrorT $ do
return (Right m)
You're reading a <- m as "assign a the value m." That notation for assignment is common in pseudocode, but it means something different in Haskell. You can read it as "Produce a value from m and bind that value to a." To be more precise, in a do block,
a <- m
...
...
is equivalent to
m >>= \a ->
do
...
...
So applying Right to a is sensible, but applying it to m gives you a monadic action wrapped in Either, which isn't usually what you're after.
There is, however, a shorter way to write that instance:
instance Error e => MonadTrans (ErrorT e) where
lift m = ErrorT (Right <$> m)
Nota Bene: ErrorT has generally been supplanted by the more generally-useful ExceptT, which doesn't have the annoying and often-irrelevant Error context. In particular, it's very often useful to have an "exception" value that doesn't actually represent an error and isn't an instance of Show.
m :: m a
Right m :: Either e (m a)
return (Right m) :: m (Either e (m a))
ErrorT $ return (Right m) :: ErrorT e m (m a)
This has the wrong type: we wanted ErrorT e m a.
Instead, when using a <- m, we have:
a :: a
Right a :: Either e a
return (Right a) :: m (Either e a)
ErrorT $ return (Right a) :: ErrorT e m a
which is OK.
(Above some value variables have the same name of type variables on the right of :: -- this is just an incident.)
Alternatives:
instance (Error e) => MonadTrans (ErrorT e) where
lift m = ErrorT $ fmap Right m
or with applicative notation,
instance (Error e) => MonadTrans (ErrorT e) where
lift m = ErrorT $ Right <$> m

What are good wrappers to transfer state change in haskell?

I am trying to implement a simple FRP backend, for my own interest.
I decided to use pure functions: so, no IO in the core. The implementation is based on signal transformer.
I already have tried two ways:
newtype SF a b = SF { listen :: [a] -> [b] }
https://gist.github.com/Heimdell/9675964#file-streamer-hs-L1
and
newtype SF a b = SF { run :: a -> (b, SF a b) }
https://gist.github.com/Heimdell/9675964#file-behaviour-hs-L1 (misnamed, sorry)
Both ways make possible to make a fold/integrate :: (a -> b -> b) -> b -> SF a b combinator for signal integration.
Both ways have a problem: Seems to be impossible to make a valid ArrowApply/Monad instance.
Stream-way: we have a list of pairs (arrow, x) - or, unziped, the pair of lists (arrows, xs).
If we will map head to the result of zipWith ($) 'em, we will loose the carried-along arrow mutation.
if we make head arrows listen xs, we will freeze the state of first arrow taken.
Explicit state-way:
instance ArrowApply Behaviour where
app =
Behaviour $ \(bf, a) ->
let (bf1, c) = bf `runBehaviour` a
in (app, c)
Here we need to somehow validly inject bf1 into app returned, which is impossible (and actually injecting by (const bf1 *** id) produces invalid behaviour analoguous to the second one from other implementation.
Is there a possible way to make a SF which allows ArrowApply instance?
P.S.: The stream-way has a memory leak in the ArrowChoice, when a branch sits unused for a long time. For now, I cannot fix that. Is it ever possible to make a no-leak version of it?
P.P.S: If one need time, he could zip it with input.
I can't find any possible instance that doesn't simply discard the state of the inner container. This isn't surprising, since the return from the pure function bound to the data should return the same thing each time the input is called, regardless of if it has been called before, which you hint at in your comments.
By itself
The only Monad instances I can come up with both discard the subsequent states for the inner container.
instance Monad (SF e) where
return a = SF . const $ (a, return a)
(>>=) sa f = SF go
where
go e =
let
(a, sa') = run sa e
sb = f a
(b, _) = run sb e
in
(b, sa' >>= f)
or
join :: SF e (SF e a) -> SF e a
join ssa = SF go
where
go e =
let
(sa, ssa') = run ssa e
(a, _) = run sa e
in
(a, join ssa')
These can be expressed more succinctly using the Monad instance for functions
instance Monad (SF e) where
return a = SF . const $ (a, return a)
(>>=) sa f = SF {
run =
do
(a, sa') <- run sa
(b, _) <- run (f a)
return (b, sa' >>= f)
}
We can look elsewhere for something a little different.
Function Monad Instance
Your newtype SF e a = SF { run :: e -> (a, SF e a) } is very close to a function from e to a. For the Monad instance for functions the only sensible >>= is to pass the argument to both the inner and outer functions. This is what we've already come up with. Let's see if we can come up with something else.
StateT
Your code is somewhat similar to the StateT monad transformer applied to the Monad instance for functions. Unfortunantly, this doesn't yield what we are looking for.
Consider the following (the StateT monad transformer):
newtype StateT s m a = StateT { runStateT :: s -> m (a, s)}
Applied to the type ((->) e) of a function that takes an argument `e.
StateT s ((->) e) a has the single constructor StateT { runStateT :: s -> e -> (a, s) }.
This differs from your type in that an initial state must be provided, and the state is tracked explicitly instead of already wrapped up in the returned next value. Let's see what the Monad instance for this would be. StateT's Monad instance is
instance (Monad m) => Monad (StateT s m) where
return a = state $ \s -> (a, s)
m >>= k = StateT $ \s -> do
~(a, s') <- runStateT m s
runStateT (k a) s'
state f = StateT (return . f)
Combined with an instance for (->) e
instance Monad ((->) e) where
return = const
(>>=) x y z = y (x z) z
We'd get the following, where the do dumps the work off onto the instance for ((->) e)
instance Monad (StateT s ((->) e) where
return a = StateT (const . (\s -> (a, s)))
m >>= k = StateT $ \s e ->
let (a, s`) = runStateT m s e
in runStateT (k a) s` e
This looks quite different. We aren't losing the history of any state. What's happening here is that the state for the inner container is being passed to it from the outer container, and the two containers must have the same type for the state for this to work. This isn't what we want at all.
Something New
What happens if we try to make something like StateT from your type? We'd like to be able to pass in the type (->) e and get a structure like yours. We'll make something called SFT m a such that SFT ((-> e) a has the same structure as SF e a.
newtype SF e a = SF { run :: e -> (a, SF e a)
newtype SFT m a = SFT { unSFT :: m (a, SFT m a) }
We can substiture a type made by applying SFT to (->) e) for SF applied to e
SF e a -- is replaced by
SFT ((->) e) a
This has a single constructor
SF { run :: e -> (a, SF e a) }
SFT { unSFT :: e -> (a, SFT ((->) e) a) }
This provides no new insight, the only Monad instance I can think of for it is almost identical to the original one.
instance Monad m => Monad (SFT m) where
return a = SFT . return $ (a, return a)
(>>=) sa f = SFT {
unSFT =
do
(a, sa') <- unSFT sa
(b, _) <- unSFT (f a)
return (b, sa' >>= f)
}

Resources