[Haskell-cafe] Stacking State on State.....

Phil pbeadling at mail2web.com
Tue Mar 3 17:28:13 EST 2009


I've had a look at your example - it's raised yet more questions in my mind!


On 02/03/2009 23:36, "Daniel Fischer" <daniel.is.fischer at web.de> wrote:


> A stupid example:
> ----------------------------------------------------------------------
> module UhOh where
> 
> import Control.Monad
> import Control.Monad.State.Lazy
> --import Control.Monad.State.Strict
> 
> 
> uhOh :: State s ()
> uhOh = State $ \_ -> undefined
> 
> uhOhT :: Monad m => StateT s m ()
> uhOhT = StateT $ \_ -> return undefined
> 
> uhOhT2 :: Monad m => StateT s m ()
> uhOhT2 = StateT $ \_ -> undefined
> 
> oy :: State s ()
> oy = State $ \_ -> ((),undefined)
> 
> oyT :: Monad m => StateT s m ()
> oyT = StateT $ \_ -> return ((),undefined)
> 
> hum :: State Int Int
> hum = do
>     k <- get
>     w <- uhOh
>     put (k+2)
>     return w
>     return (k+1)
> 
> humT :: Monad m => StateT Int m Int
> humT = do
>     k <- get
>     w <- uhOhT
>     put (k+2)
>     return w
>     return (k+1)
> 
> 
> humT2 :: Monad m => StateT Int m Int
> humT2 = do
>     k <- get
>     w <- uhOhT2
>     put (k+2)
>     return w
>     return (k+1)
> 
> 
> whoa n = runState (replicateM_ n hum >> hum) 1
> 
> whoaT n = runStateT (replicateM_ n humT >> humT) 1
> 
> whoaT2 n = runStateT (replicateM_ n humT2 >> humT2) 1
> 
> yum :: State Int Int
> yum = do
>     k <- get
>     w <- oy
>     put (k+2)
>     return w
>     return (k+1)
> 
> yumT :: Monad m => StateT Int m Int
> yumT = do
>     k <- get
>     w <- oyT
>     put (k+2)
>     return w
>     return (k+1)
> 
> hoha n = runState (replicateM_ n yum >> yum) 1
> 
> hohaT n = runStateT (replicateM_ n yumT >> yumT) 1
> 
> oops m = runState m 1
> ----------------------------------------------------------------------
> 
> What happens with
> 
> whoa 10
> hoha 10
> oops (whoaT 10)
> oops (whoaT2 10)
> oops (hohaT 10)
> 
> respectively when the Lazy or Strict library is imported?
> Answer first, then test whether you were right.

OK, I had a think about this - I'm not 100% clear but:

UhOh - OK for lazy, Bad for Strict.  "undefined" 'could' be of the form
(a,s) so the lazy accepts it, but the strict version tries to produce (a,s)
out of undefined and fails.

Oy - Both are OK here.  The pair form is retained and neither will go as far
as to analyse the contents of either element of the pair, as neither is
used.

UhOhT - OK for lazy, Bad for Strict. Same as Oh UhOh, but as we have
transformer we return inside a Monad.

UhOhT2 - Bad for both - transformers should return a Monad.

OyT - Same as Oy, but returned inside a monad.


The thing which confuses me is why we care about these functions at all hum,
yum, etc.  Although these inspect the State Monads above they stick the
values in to 'w' which is never used (I think), because the first return
statement just produces "M w" which is not returned because of the return
(k+1) afterwards??

Because lazy and strict are only separated by the laziness on the bind
between contiguous hum and yum states, I would have thought that laziness on
w would have been the same on both.

Hmmm. But I suppose each call to hum and yum is increment stating in it's
corresponding UhOh and Oy function.  Thus causing these to be strictly
evaluated one level deeper.... In which case I do understand.

We have:

hum >> hum >> hum  .....

And At each stage we are also doing UhOh >> UhOh >> UhOh inside the hums?

Is this right, I'm not so sure?  I'm in danger of going a bit cross-eyed
here!


> 
>> This means that each new (value,state) is just passed around as a thunk and
>> not even evaluated to the point where a pair is constructed - it's just a
>> blob, and could be anything as far as haskell is concerned.
> 
> Not quite anything, it must have the correct type, but whether it's
> _|_, (_|_,_|_), (a,_|_), (_|_,s) or (a,s) (where a and s denote non-_|_
> elements of the respective types), the (>>=) doesn't care. Whether any
> evaluation occurs is up to (>>=)'s arguments.
> 

By correct type you mean that it must *feasibly* be a pair... But the lazy
pattern matching doesn't verify that it *is* a pair.  Thus if we returned
something that could never be a pair, it will fail to compile, but if it is
of the form X or (X,X) it won't check any further than that, but if it was
say [X] that wouldn't work even for lazy - haskell doesn't trust us that
much!?

>> It follows that each new state cannot evaluated even if we make newStockSum
>> strict as (by adding a bang) because the state tuple newStockSum is wrapped
>> in is completely unevaluated - so even if newStockSum is evaluated INSIDE
>> this blob, haskell will still keep the whole chain.
> 
> Well, even with the bang, newStockSum will only be evaluated if somebody looks
> at what mc delivers. In the Strict case, (>>=) does, so newStockSum is
> evaluated at each step.

When you say 'looks' at it do you mean it is the final print state on the
result that ultimately causes the newStockSum to be evaluated in the lazy
version?  Thus we are saying we evaluate it only because we know it is
needed.  
However in the strict case, the fact that newStockSum is used to evaluate
the NEXT newStockSum in the subsequent state (called via the bind) is enough
to force evaluation, even if the result of the subsequent state is not used?

> In the Lazy case, (>>=) doesn't, replicateM_ doesn't,
> so newStockSum won't be evaluated inside the blob, if it were, it would force
> the evaluation of the previous pair and almost everything else, then there
> would have been no problem. What the bang does in the lazy case is to keep
> the thunk for the evaluation of the states a little smaller and simpler, so
> the evaluation is a bit faster and uses less memory, but not much (further
> strictness elsewhere helps, too, as you've investigated).
> 

So in the lazy state the bang will evaluate things that are local to THIS
state calculation, but it won't force evaluation of previous states.  Thus
expression remaining could be simplified as far as possible without
requiring the previous MonteCarlo state or the previous BoxMuller state.

  



More information about the Haskell-Cafe mailing list