Hi,

I've encountered an interesting issue with GHC 6.12.1 and 2 in which a
small program compiles quickly without using loads of memory with
optimization turned off, but with optimization (-O1) turned on, GHC's
memory usage becomes very high (and compilation takes much much
longer).

$ time ghc -c -O0 Tst.hs

real    0m0.107s
user    0m0.073s
sys     0m0.035s

$ time ghc -c -O1 Tst.hs

real    0m38.605s
user    0m36.669s
sys     0m1.923s

Memory used by GHC looks like it tops out at 3G (in the -O1 case).

Constraining the heap size to 1G causes compilation to fail:

$ ghc +RTS -M1g -RTS -c -O1 Tst.hs
Heap exhausted;
Current maximum heap size is 1073741824 bytes (1024 MB);
use `+RTS -M<size>' to increase it.

(whereas, without optimization, a heap of 16m is sufficient)

The module being compiled is (probably deceptively) simple:

module Tst where
import Merge
data Rec1 = Rec1 !Int
mkRec1 v = mk $ merge v () where mk (Tagged i :* ()) = Rec1 i

but the devil is in the details of 'merge' (attached) which merges
heterogeneous lists of values, using a lot of type level programming
with type families.  Does this sound like an known, open issue?  I was
unable to find anything in GHC Trac that looked similar.

Thanks,
Rob

Attachment: Merge.hs
Description: Binary data

_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to