Common subexpressions are not optimized to single one?
Koji Nakahara
yu- at div.club.ne.jp
Wed Dec 3 03:29:14 EST 2003
Hi,
I'm wondering about the optimization of ghc. I thought that since
functions are pure in haskell, compiler can/do factorize common
subexpressions when it optimizes a code. But the result of the following
experiment looks negative; "g 10 100" is caluculated twice.
Am I missing something? If not,
What prevents ghc from performing that optimization?
Should I always factorize common subexpressions manually(using let or where)?
---
$ cat op.hs
module Main
where
import System.IO.Unsafe
foreign import ccall "count" io_count:: IO Int
f :: Int -> IO Int
f x = do {y <- io_count; return $ x + y}
g :: Int -> Int -> Int
g x y = unsafePerformIO $ do {z <- f x; return $ z + y}
main = do print (g 10 100, g 10 100)
$
$ cat ffi_test_c.c
static int counter = 0;
int count() {return counter++;}
$
$ gcc -c ffi_test_c.c;ghc -O2 -ffi op.hs;ghc -o op_test op.hs ffi_test_c.o
$ ./op_test
(110,111)
---
I want to use some C functions from haskell each of which is not pure but
the result of their sequential combination is pure. I'm planning to write
some functions like g above(but more complex and actually pure) and
considering the optimization of the code using them.
Thanks in advance.
Koji Nakahara
More information about the Haskell-Cafe
mailing list