[Haskell-cafe] Re: evaluation semantics of bind

Gleb Alexeyev gleb.alexeev at gmail.com
Thu Feb 5 10:53:52 EST 2009


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.

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?
If no, why would GHC want to do this optimization for standard IO?






More information about the Haskell-Cafe mailing list