
Hi, folks Trying to profile the modules, those contain a template-haskell splices, I have ran into problem - GHC6.4 (win2K) returns an error message and then stops. Without the "-prof" option all works fine. Is there a way to bypass this inconsistency? Example below illustrates the problem: ============================ {-# OPTIONS_GHC -fth #-} module Main where import MainTH main :: IO () main = putStrLn . show . fact $ 100 fact :: Integer -> Integer fact n = $(thFact "n") ============================ module MainTH where import Language.Haskell.TH thFact :: String -> ExpQ thFact s = appE (dyn "product") (arithSeqE (fromToR (litE . integerL $ 1) (dyn s))) preview :: IO () preview = runQ (thFact "x") >>= putStrLn . pprint ============================
ghc --make -prof Main.hs Chasing modules from: Main.hs Compiling MainTH ( ./MainTH.hs, ./MainTH.o ) Compiling Main ( Main.hs, Main.o ) Loading package base-1.0 ... linking ... done. Loading package haskell98-1.0 ... linking ... done. Loading package template-haskell-1.0 ... linking ... done. ghc: ./MainTH.o: unknown symbol `_era'
With function "MainTH.preview" excluded from export list, final phrase were ghc: ./MainTH.o: unknown symbol `_entering_PAP'