[Haskell-cafe] Retrieving inner state from outside the transformer
phil at beadling.co.uk
phil at beadling.co.uk
Sat Aug 1 14:06:45 EDT 2009
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)
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20090801/2e104e25/attachment.html
More information about the Haskell-Cafe
mailing list