
Let's put it this way: suppose you have two data types, say, Int and String; a value s of type String and a function f :: String -> (Int -> String) -> String This could be anything - may be, a function which looks for the first character '#' in it's first argument and replaces it with the second argument applied to the position where it's found; so f "abc#" (\n -> replicate n 'q') = "abcqqq" It could be anything else, of course. Now, would you expect an optimizer to transform f s (\x -> s) to s? I don't think so. f s (\x -> s) and s are clearly distinct and there is no reason to transform one to the other. Now, let's change notation a bit. First of all, let's denote our string s by getChar. Well, it's our string and we can name it with what name we want - especially if we forget for a moment that getChar is already defined. So, for a moment we assume that getChar is defined like this: getChar = "abc#" Therefore, f getChar (\x -> getChar) is NOT equivalent to getChar. Right? Let's change notation even more. Let's denote our function by (>>=): (>>=) getChar (\x -> getChar) is NOT equal to getChar By Haskell rules we can use >>= as infix operator: getChar >>= (\x -> getChar) is NOT equal to getChar Now, in your example, instead of Int and String we have Char and IO Char. Does that matter? In all the above we didn't use the fact that our types are Int and String; the very same applies to Char and (IO Char) as well. On 5 Feb 2009, at 19:18, Gregg Reynolds wrote:
On Thu, Feb 5, 2009 at 9:53 AM, Gleb Alexeyev
wrote: Let's imagine that IO datatype is defined thus: {-# LANGUAGE GADTs #-} {-# LANGUAGE NoImplicitPrelude #-}
import Prelude(Monad, Char) data IO a where GetChar :: IO Char Bind :: IO a -> (a -> IO b) -> IO b
getChar = GetChar (>>=) = Bind
It is perfectly possible to construct IO actions as values of this data type and execute them by some function evalIO :: IO -> Prelude.IO with the obvious definition. Now the question arises: do you think getChar >>= \x -> getChar would be optimized to getChar by compiler?
I must be misunderstanding something. I don't know if it would be optimized out, but I see no reason why it couldn't be. There's no data dependency, right?
-g _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe