
2009/2/9 Gregg Reynolds
On Sun, Feb 8, 2009 at 6:25 PM, Richard O'Keefe
wrote: On 6 Feb 2009, at 4:20 am, Gregg Reynolds wrote:
However, consider:
getChar >>= \x -> getChar
An optimizer can see that the result of the first getChar is discarded and replace the entire expression with one getChar without changing the formal semantics.
But the result of the first getChar is *NOT* discarded. **As an analogy**, think of the type IO t as (World -> (t,World)) for some hidden type World, and getChar w = (c, w') -- get a character c out of world w somehow, -- changing w to w' as you go (f >>= g) w = let (v,w') = f w in (g v) w'
In this analogy, you see that the result of getChar is a value of type IO Char (not of type Char), and that while the character part of the result of performing the result of getChar may be discarded, the "changed world" part is NOT.
That's an implementation detail. It doesn't account for other possible IO implementations.
My original question was motivated by the observation that a human reader of an expression of the form "e >>= f" , on seeing that f is constant, may pull the constant value out of f, disregard e and dispense with the application f e. So can a compiler, unless IO expressions are involved, in which case such optimizations are forbidden. I wondered if that was due to the semantics of >>= or the semantics of IO.
Neither. It's because the expression "e >>= f" is not "f e". As far as
Haskell is concerned, >>= is just a higher-order function. You can't
arbitrarily replace "foo bar (const baz)" with "baz", unless it turns
out that foo = \x y -> y x.
Perhaps you're thinking of the monad law,
forall x f. return x >>= f = f x
The presence of "return" is important. Among other things, there is no
x such that getChar = return x. That's because getChar has (or,
rather, causes when interpreted by the RTS) side-effects, whereas
"return x" is pure.
Here's some code you can try on your own:
data IO a = Return a | Get (Char -> IO a) | Put Char (IO a)
instance Monad IO where
return = Return
Return a >>= f = f a
Get k >>= f = Get (\c -> k c >>= f)
Put c k >>= f = Put c (k >>= f)
getChar :: IO Char
getChar = Get (\c -> Return c)
putChar :: Char -> IO ()
putChar c = Put c (Return ())
Now, if the compiler sees "getChar >>= \_ -> getChar", it *can*
optimize out the >>=. But the result would be "Get (\_ -> Get (\c ->
Return c))", which is not equivalent to getChar. Neither IO semantics
nor monad semantics are involved.
--
Dave Menendez