[Haskell-cafe] Re: evaluation semantics of bind

ChrisK haskell at list.mightyreason.com
Thu Feb 5 20:20:33 EST 2009


Jonathan Cast wrote:
> On Fri, 2009-02-06 at 00:51 +0100, Peter Verswyvelen wrote:
>> On Thu, Feb 5, 2009 at 8:20 PM, ChrisK <haskell at list.mightyreason.com>
>> wrote:
>>         Since this is strict there is no laziness and the code must
>>         evaluate the input and output "State RealWorld" to ensure they
>>         are not bottom or error.
> 
>> Interesting. I also thought it was the passing of the RealWorld that
>> caused the sequencing, I never realized that the strictness played an
>> important role here. 
> 
>> So what would happen if it would be lazy instead of strict? What kind
>> of craziness would occur?
> 
> The order of side effects would be demand-driven, rather than
> order-of-statement driven.  So if I said:
[snip]
> Essentially, the program would act as if every statement was wrapped up
> in an unsafeInterleaveIO.
> 
> jcc

I do not think so.  Consider 
http://darcs.haskell.org/packages/base/GHC/IOBase.lhs to see unsafeInterleaveIO:

> unsafeInterleaveIO m = unsafeDupableInterleaveIO (noDuplicate >> m)
> unsafeDupableInterleaveIO (IO m)
>   = IO ( \ s -> let
>                    r = case m s of (# _, res #) -> res
>                 in
>                 (# s, r #))

And Control.Monad.State.Lazy which is the non-strict State monad:

> newtype State s a = State { runState :: s -> (a, s) }

> instance Monad (State s) where
>     return a = State $ \s -> (a, s)
>     m >>= k  = State $ \s -> let
>         (a, s') = runState m s
>         in runState (k a) s'

And you can see that the data dependence is broken in unsafeInterleaveIO by _, 
and not broken in State.Lazy.  But neither s nor s' are not forced to WHNF.

What you can do State.Lazy is put an bottom into the state.  Or you can put an 
unevaluated thunk into the state, and if it gets replaced later then you never 
paid to evaluate it.

But the sequencing is retained.  One could make an unsafeInterleaveIO for state:

> interleaveState :: State s a -> State s a
> interleaveState (State m) = State ( \ s -> let (a,_) = runState m s
>                                            in (a,s) )

Now the dependency chain is broken in the above, due to the _ being ignored.

Cheers,
   Chris



More information about the Haskell-Cafe mailing list