[Template-haskell] Profiling with Template Haskell

Sean Seefried sseefried@cse.unsw.EDU.AU
Fri, 18 Jul 2003 20:09:28 +1000 (EST)


Hi all,

I'd just like to find out what your experiences with profiling TH
programs are? I'm not sure GHC-6.0 accomodate profiling when Template
Haskell is involved. A really simple example that doesn't work
is:

ghc -prof -fglasgow-exts -make Main.hs

applied to

-----------------
{- Splices.hs -}
module Splices
where

import Language.Haskell.THSyntax

d_fun =
    [d|
     fun = putStrLn "I am a function"
     |]

-----------------
{- Main.hs -}

module Main
where
import Splices

$(d_fun)

main = fun

----------------

The output is :

Chasing modules from: Main.hs
Skipping  Splices          ( Splices.hs, ./Splices.o )
Compiling Main             ( Main.hs, ./Main.o )
Loading package base ... linking ... done.
Loading package haskell98 ... linking ... done.
Loading package haskell-src ... linking ... done.

./Splices.o: unknown symbol `_CCCS'


I'll bet that _CCCS is a cost center symbol that is (correctly) added
to Splices.o. This symbol is present in many of the standard
libraries (compiled with profiling support enabled. e.g. libHSbase_p.a
contains the symbol)

Now I know that profiling splicing doesn't make too much sense.  That
is not what I wish to do though. I wish to profile the final
executable.

I'm aware that when splicing much of the functionality of GHCi is
used. Consider the three lines from the input above:

Loading package base ... linking ... done.
Loading package haskell98 ... linking ... done.
Loading package haskell-src ... linking ... done.

I think these are spat out from Linker.lhs. (It resides in the
ghc/compiler/ghci directory of the GHC source.)

Of course, at this point in compilation "_CCCS" is undefined. Is
there anyway that we can get the linker to ignore profiling symbols
during this phase of the compilation? How are we profile programs
that use Template Haskell otherwise?

Sean