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

Daniel Fischer daniel.is.fischer at web.de
Wed Mar 4 11:31:17 EST 2009


Am Dienstag, 3. März 2009 23:28 schrieb Phil:
> 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.

Correct.

>
> 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.

Correct.

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

Correct.

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

Mostly correct, but, using Lazy:
*UhOh> oops (whoaT2 10)
((22,23),*** Exception: Prelude.undefined
*UhOh> evalState (runStateT humT2 4) 0
(5,6)
*UhOh> let putI :: Int -> State Int (); putI = put
*UhOh> let see = do { k <- get; w <- uhOhT2; put (k+2); lift (putI 4); return 
w; return (k+1) }
*UhOh> oops $ runStateT see 3
((4,5),4)

So if the inner monad is lazy enough, it can happily pass over the undefined.
Let's look at what happens if we bind uhOhT2 to f :: () -> StateT s m b (where 
m is some monad).
uhOhT2 >>= f
	= StateT $ \so -> do
		~(a,so') <- runStateT uhOhT2 so
		runStateT (f a) so'
	= StateT $ \so -> do
		~(ao,so') <- undefined
		runStateT (f a) so'
	= StateT $ \so -> undefined >>= \x -> let (a,so') = x in runStateT (f a) so'

Now if f doesn't inspect a and runStateT (f a) doesn't inspect so', the only 
one left to raise an objection is the (>>=) of the inner monad m (let 
bindings are lazy, so the let (a,so') = x won't fail on undefined, only if f 
needs to analyse a or runStateT (f a) needs to analyse so' will failure 
occur).
If m is Maybe or [], the inner bind fails and so everything fails.
But if m is a lazy State monad, we see that

undefined >>= g
	= State $ \si -> let (b, si') = runState undefined si in runState (g b) si'

and only if g needs to analyse b or runState (g b) needs to analyse si' we 
will fail.

When g is \x -> let (a,so') = x in runStateT (f a) so', it only needs to 
analyse b if f needs to analyse a or runStateT (f a) needs to analyse so'.
Since I've avoided that, the put repairs the outer state (and in 'see', the 
'lift $ putI 4' also repairs the inner state) and no harm's done.

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

Sure.

>
> 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??

Yes, the w is never really used, makes no difference at all.

>
> 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.

Yes.

>
> 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.

I'm sorry, I don't understand the above :(

In oy(T), we do something moderately bad, we inject an undefined into the 
state. But we fix it before anybody had a chance to see it in yum(T) by 
immediately following it by a put. It's a bit like 
map (const 1) $ map (const undefined) list
, the intermediate result would be harmful, but it doesn't persist.

In uhOh(T), we do something bad, we let the complete (value,state) pair be 
undefined. If nobody looks whether it's a real pair before we fix it by the 
put, again no harm is done. The strict state monad checks if it's a real pair 
(whatever, whatever else), finds that it isn't and bombs out. The lazy state 
monad says "whatever, I'll assume it's okay until I need to inspect it". It 
never needs to inspect it, so it's ignored.

In uhOhT2, we do something even worse, we let the inner-monadic value be 
undefined. The strict state transformer monad says "give me a pair", 
undefined can't, bomb out. The lazy state transformer monad says "if the 
inner monad's bind asks you for a pair, hand it over, please" and passes the 
undefined to the inner monad's bind without inspecting it.

>
> 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!

We're doing an uhOh sandwiched between a get and a put in each hum, so it's 
rather
get >> uhOh >> put x >> get >> uhOh >> ...

Now the point is, in the lazy monad we have (uhOh >> put x) === put x, but not 
in the strict monad.

>
> >> 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,

Yes, it may have type forall a. a, or it may have type forall a b. (a,b), or 
it may have a more restricted pair type. If the bound function k has type

a -> State s b

, the type of the thing must be unifyable with (a,s). If it's not, the code 
won't compile. If it is, the lazy pattern matching will not even verify that 
the thing exists (cf. uhOhT2).

> 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?

In this case, yes. In principle, you could have something that forces the 
evaluation before, e.g. if you replace replicateM_ with a stricter version,

replicateM'_ :: (Monad m) => Int -> m a -> m ()
replicateM'_ k a = sequence'_ (replicate k a)

sequence'_ :: (Monad m) => [m a] -> m ()
sequence'_ (x:xs) = do
    !a <- x
    sequence'_ xs
sequence'_ [] = return ()

, the sequence'_ inspects the result () of mc. With the bang on newStockSum, 
this also forces the evaluation of that, even with Control.Monad.State.Lazy. 
In the few test I ran, the combination State.Lazy and replicateM'_ was about 
6% slower and allocated ~8% more than State.Strict and replicateM_.

If you leave off the bang on newStockSum, replicateM'_ doesn't help State.Lazy 
(perhaps a tiny little bit).


>  Thus we are saying we evaluate it only because we know it is
> needed.

That's the point of lazy evaluation. And by using strictness annotations in 
the right places, we help the compiler because we may know that something 
will be needed although the compiler can't ascertain it alone.

> 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?

With the bang, yes.

>
> > 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.

In the lazy state, the bang will cause evaluation of newStockSum when somebody 
says "hand me a pair, not a blob". Then mc says "Okay, a pair. Now what do I 
put in the pair? Let me see. Ah, the first component is (), no sweat. And the 
second component is newStockSum - oh, that's strict, so I have to evaluate it 
before I can put it into the pair." And thus everything else is forced and 
happiness ensues :)

Cheers,
Daniel




More information about the Haskell-Cafe mailing list