Retrieving inner state from outside the transformer

Hi, I've hit a brick wall trying to work out, what should be (and probably is!) a simple problem. I have a StateT stack (1 State monad, 2 StateT transformers) which works fine and returns the result of the outer monad. I thought I understood this fine, but perhaps not. My understanding is that the result returned by the inner-most monad is always 'transformed' by the outer monads and thus the result you get is that computed in the outer transformer. The problem I have is now I'd like not only to get the final state of the outer most transformer, but I'd also like to know the final states of the the inner StateT and the inner State at the end of the computation (so that at a later point in time I can reinitialize a similar stack and continue with the same set of states I finished with). So I figured I could have a separate (parent) State Monad (not part of this stack) that would store the final state of the sequence below. I figured it couldn't be part of this stack, as one computation on the stack does not lead to one result in the parent State Monad; it is only the end states of the sequence I care about. Anyway, currently I just have the stack evaluated as below. Is there anyway from outside of the computation that I can interrogate the states of the inner layers? The only way I can see to do this is inside the outer monad itself. As I'm not using the result I could use 'lift get' and 'lift lift get' to make the outer transformer return the two inner states as it's result. I could ignore this result for the first (iterations-1) and bind a final iteration which uses replicateM instead of replicateM_. This strikes me as pretty horrible tho! So, in the example below if I want to modify the 'result' function so it returns no only the outer state, but also the two inners states as a tuple (Double,Double,Double) is there an easier way of doing this? result :: RngClass a => NormalClass b => a -> b -> MonteCarloUserData -> Double result initRngState initNormState userData = evalState a initRngState where a = evalStateT b initNormState b = execStateT ( do replicateM_ (iterations userData) (mc userData)) 0 Any advice greatly appreciated! Thanks, Phil.

On Thu, Jul 30, 2009 at 7:06 PM, Phil
Hi,
I've hit a brick wall trying to work out, what should be (and probably is!) a simple problem.
I have a StateT stack (1 State monad, 2 StateT transformers) which works fine and returns the result of the outer monad. I thought I understood this fine, but perhaps not. My understanding is that the result returned by the inner-most monad is always 'transformed' by the outer monads and thus the result you get is that computed in the outer transformer.
What I would do is not use transformers - I would have computations of type 'State MyState a' where 'MyState' would be something like: data MyState = MyState { component_one :: TypeOne , component_two :: TypeTwo , component_three :: TypeThree } instead of three separate transformers/monads for each data type. I would then have helper functions: getThingOne :: State MyState TypeOne setThingOne :: TypeOne -> State MyState () modifyThingOne :: (TypeOne -> TypeOne) -> State MyState TypeOne etc. You'll want to pick better names for your types and helper functions as suits your program. Antoine

StateT is really simple, so you should be able to figure it out:
runStateT :: StateT s m a -> s -> m (a,s)
runState :: State s a -> s -> (a,s)
So if you have
m :: StateT s1 (StateT s2 (State s3)) a
runStateT m :: s1 -> StateT s2 (State s3) (a,s)
\s1 s2 s3 -> runState (runStateT (runStateT m s1) s2) s3)
:: s1 -> s2 -> s3 -> (((a,s1), s2), s3)
A different way to do it:
transformStateT :: (m1 (a,s) -> m2 (a,s)) -> StateT s m1 a -> StateT s m2 a
transformStateT f sm1 = StateT (f . runStateT sm1)
upgradeStateT :: StateT s1 (State s2) a -> State (s1,s2) a
upgradeStateT m = State $ \(s1,s2) ->
let ((a,s1'), s2') = runState (runStateT m s1) s2
in (a, (s1', s2'))
upgradeStateT2 :: StateT s1 (StateT s2 (State s3)) a -> State (s1,(s2,s3)) a
upgradeStateT2 = upgradeStateT . transformStateT upgradeStateT
You should be able to write downgradeStateT similarily to get back to
your monad stack representation.
-- ryan
On Thu, Jul 30, 2009 at 5:06 PM, Phil
Hi,
I've hit a brick wall trying to work out, what should be (and probably is!) a simple problem.
I have a StateT stack (1 State monad, 2 StateT transformers) which works fine and returns the result of the outer monad. I thought I understood this fine, but perhaps not. My understanding is that the result returned by the inner-most monad is always 'transformed' by the outer monads and thus the result you get is that computed in the outer transformer.
The problem I have is now I'd like not only to get the final state of the outer most transformer, but I'd also like to know the final states of the the inner StateT and the inner State at the end of the computation (so that at a later point in time I can reinitialize a similar stack and continue with the same set of states I finished with).
So I figured I could have a separate (parent) State Monad (not part of this stack) that would store the final state of the sequence below. I figured it couldn't be part of this stack, as one computation on the stack does not lead to one result in the parent State Monad; it is only the end states of the sequence I care about.
Anyway, currently I just have the stack evaluated as below. Is there anyway from outside of the computation that I can interrogate the states of the inner layers? The only way I can see to do this is inside the outer monad itself. As I'm not using the result I could use 'lift get' and 'lift lift get' to make the outer transformer return the two inner states as it's result. I could ignore this result for the first (iterations-1) and bind a final iteration which uses replicateM instead of replicateM_.
This strikes me as pretty horrible tho!
So, in the example below if I want to modify the 'result' function so it returns no only the outer state, but also the two inners states as a tuple (Double,Double,Double) is there an easier way of doing this?
result :: RngClass a => NormalClass b => a -> b -> MonteCarloUserData -> Double result initRngState initNormState userData = evalState a initRngState
where a = evalStateT b initNormState
b = execStateT ( do replicateM_ (iterations userData) (mc userData)) 0
Any advice greatly appreciated!
Thanks,
Phil.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Thanks very much for both replies. I think I get this now. Simply, my choice of evaluation functions (evalStateT, execStateT and execState) ensured that the states are not returned. It was obvious. I can get this working, but I have one more more question to make sure I actually understand this. Below is a very simple and pointless example I wrote to grasp the concept. This returns ((1,23),21) which is clear to me. import Control.Monad.State myOuter :: StateT Int (State Int) Int myOuter = StateT $ \s -> do p <- get return (s,p+s+1) main :: IO() main = do let innerMonad = runStateT myOuter 1 y = runState innerMonad 21 print y Thus we are saying that a=(1,23) and s=21 for the state monad, and that a=1 and s=23 for the state transformer. That is the return value of the state monad is the (a,s) tuple of the transformer and it's own state is of course 21. This got me thinking - the return value's type of the state monad is dictated by the evaluation function used on the state transformer - it could be a, s, or (a,s) depending which function is used. Thus if I edit the code to to: do let innerMonad = evalStateT myOuter 1 I get back (1,21) - which is the problem I had - we've lost the transformer's state. Look at the Haskell docs I get: evalStateT :: Monad m => StateT s m a -> s -> m a runStateT :: s -> m (a, s) So the transformer valuation functions are returning a State monad initialized with either a or (a,s). Now I know from messing around with this that the initialization is the return value, from the constructor: newtype State s a = State { runState :: s -> (a, s) } Am I right in assuming that I can read this as: m (a,s_outer) returned from runStateT is equivalent to calling the constructor as (State s_inner) (a,s_outer) This makes sense because in the definition of myOuter we don't specify the return value type of the inner monad: myOuter :: StateT Int (State Int) Int The problem is whilst I can see that we've defined the inner monad's return value to equal the *type* of the transformer's evaluation function, I'm loosing the plot trying to see how the *values* returned by the transformer are ending up there. We haven't specified what the state monad actually does? If I look at a very simple example: simple :: State Int Int simple = State $ \s -> (s,s+1) This is blindly obvious, is I call 'runState simple 8', I will get back (8,9). Because I've specified that the return value is just the state. In the more original example, I can see that the 'return (s,p+s+1)' must produce a state monad where a=(1,23), and the state of this monad is just hardcoded in the code = 21. I guess what I'm trying to say is - where is the plumbing that ensures that this returned value in the state/transformer stack is just the (a,s) of the transformer? I have a terrible feeling this is a blindly obvious question - apologies if it is! Thanks again! Phil. On 31 Jul 2009, at 04:39, Ryan Ingram wrote:
StateT is really simple, so you should be able to figure it out:
runStateT :: StateT s m a -> s -> m (a,s) runState :: State s a -> s -> (a,s)
So if you have m :: StateT s1 (StateT s2 (State s3)) a
runStateT m :: s1 -> StateT s2 (State s3) (a,s)
\s1 s2 s3 -> runState (runStateT (runStateT m s1) s2) s3) :: s1 -> s2 -> s3 -> (((a,s1), s2), s3)

I am not sure I entirely understand your question; it sounds like you are confused and thus your question is a bit confused. So instead, I'll explain in a bit more detail. A common pattern in Haskell is that you have a type that you want to perform some operations on, and then afterwards you "observe" the type to convert it to some simpler type that no longer has those operations. To see why the "observation" is important, consider this type:
newtype StupidT s m a = StupidT ()
Would you believe that StupidT is a state monad transformer?
instance Monad StupidT s m where return _ = StupidT () StupidT () >>= f = StupidT () instance MonadState s (StupidT s m) where get = StupidT () put _ = StupidT () instance MonadTrans (StupidT s) where lift _ = StupidT ()
StupidT follows all the laws for these typeclasses, because they all have to do with observational equality of different sets of operations. Since all operations are equal, the laws all trivially hold. For example: Proof: get >>= put = return () (this is one of the laws every MonadState needs to fulfill) get >>= put apply (>>=) = StupidT () unapply return = return () All of the other laws are proved similarily. Obviously, you can't do much with StupidT; the thing that makes StateT useful is its observation function "runStateT" runStateT :: StateT s m a -> (s -> m (a,s)) which converts from (StateT s m a), into (s -> m (a,s)). You'll often find that the most elegant implementation of a type in Haskell is to use the observation function's return type as the representation type of the object! So since we want runStateT with this particular type, we just make StateT hold that type:
newtype StateT s m a = StateT { runStateT :: s -> m (a,s) }
Now, of course, we have to implement all the operations we care about (return, (>>=), get, put, lift), such that they obey the laws those operations are supposed to fulfill, but implementing the observation function is trivial! So, how does the plumbing convert the "s" you give it into a "m (a,s)" result? Simple, there is no plumbing. You just call the function! Of course, there is some plumbing in the implementation of the operations on the transformer:
instance Monad m => Monad (StateT s m) where return a = StateT $ \s -> return (a,s) m >>= f = StateT $ \s0 -> do (a, s1) <- runStateT m s0 (b, s2) <- runStateT (f a) s1 return (b,s2)
instance Monad m => MonadState s (StateT s m) where get = StateT $ \s -> return (s,s) put s = StateT $ \_ -> return ((), s)
instance MonadTrans (StateT s) where lift m = StateT $ \s -> do a <- m return (a,s)
You should notice that all this makes runStateT "just work"; there's
no need to call additional code to get the (s -> m (a,s)) back out of
the StateT. You should also notice that these are the *only*
type-correct, non-_|_-using implementations for most of the functions;
the only places where we could make a semantic error that wasn't also
a type error are putting the wrong states through (put) and (>>=). By
choosing a representation that matches the observable value we want,
implementing the operations becomes much simpler!
-- ryan
On Sat, Aug 1, 2009 at 11:06 AM,
Thanks very much for both replies. I think I get this now. Simply, my choice of evaluation functions (evalStateT, execStateT and execState) ensured that the states are not returned. It was obvious. I can get this working, but I have one more more question to make sure I actually understand this. Below is a very simple and pointless example I wrote to grasp the concept. This returns ((1,23),21) which is clear to me. import Control.Monad.State myOuter :: StateT Int (State Int) Int myOuter = StateT $ \s -> do p <- get return (s,p+s+1) main :: IO() main = do let innerMonad = runStateT myOuter 1 y = runState innerMonad 21 print y Thus we are saying that a=(1,23) and s=21 for the state monad, and that a=1 and s=23 for the state transformer. That is the return value of the state monad is the (a,s) tuple of the transformer and it's own state is of course 21. This got me thinking - the return value's type of the state monad is dictated by the evaluation function used on the state transformer - it could be a, s, or (a,s) depending which function is used. Thus if I edit the code to to: do let innerMonad = evalStateT myOuter 1 I get back (1,21) - which is the problem I had - we've lost the transformer's state. Look at the Haskell docs I get: evalStateT :: Monad m => StateT s m a -> s -> m a runStateT :: s -> m (a, s) So the transformer valuation functions are returning a State monad initialized with either a or (a,s). Now I know from messing around with this that the initialization is the return value, from the constructor: newtype State s a = State { runState :: s -> (a, s) } Am I right in assuming that I can read this as: m (a,s_outer) returned from runStateT is equivalent to calling the constructor as (State s_inner) (a,s_outer) This makes sense because in the definition of myOuter we don't specify the return value type of the inner monad: myOuter :: StateT Int (State Int) Int
The problem is whilst I can see that we've defined the inner monad's return value to equal the *type* of the transformer's evaluation function, I'm loosing the plot trying to see how the *values* returned by the transformer are ending up there. We haven't specified what the state monad actually does? If I look at a very simple example: simple :: State Int Int simple = State $ \s -> (s,s+1) This is blindly obvious, is I call 'runState simple 8', I will get back (8,9). Because I've specified that the return value is just the state. In the more original example, I can see that the 'return (s,p+s+1)' must produce a state monad where a=(1,23), and the state of this monad is just hardcoded in the code = 21. I guess what I'm trying to say is - where is the plumbing that ensures that this returned value in the state/transformer stack is just the (a,s) of the transformer?
I have a terrible feeling this is a blindly obvious question - apologies if it is!
Thanks again!
Phil.
On 31 Jul 2009, at 04:39, Ryan Ingram wrote:
StateT is really simple, so you should be able to figure it out:
runStateT :: StateT s m a -> s -> m (a,s) runState :: State s a -> s -> (a,s)
So if you have m :: StateT s1 (StateT s2 (State s3)) a
runStateT m :: s1 -> StateT s2 (State s3) (a,s)
\s1 s2 s3 -> runState (runStateT (runStateT m s1) s2) s3) :: s1 -> s2 -> s3 -> (((a,s1), s2), s3)
participants (4)
-
Antoine Latter
-
Phil
-
phil@beadling.co.uk
-
Ryan Ingram