[Haskell-cafe] Retrieving inner state from outside the transformer

Ryan Ingram ryani.spam at gmail.com
Thu Jul 30 23:39:45 EDT 2009


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<phil at beadling.co.uk> wrote:
> 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 at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>


More information about the Haskell-Cafe mailing list