no time profiling on my MacBookPro8,1

For this vanilla program
module Main where
main = print $ fib 40
fib 0 = 1 fib 1 = 1 fib n = fib (n - 1) + fib (n - 2)
with these commands $ ghc -prof -auto-all -rtsopts -O --make Main.hs -o Main $ ./Main +RTS -p all of the %time cells in the generated Main.prof file are 0.0, as is the total time count (0.00 secs and 0 ticks). The %alloc cells seem normal. Andy Gill noticed that if you compile with -threaded, the %time cells seem normal. I scanned the GHC Trac tickets specific to Mac OS X, but saw no titles that looked similar. Is this a known issue? Thanks.

Whoops: I'm running Haskell Platform 2011.2.0.1.
OS X 10.6.7
i686-apple-darwin10-gcc-4.2.1 (GCC) 4.2.1 (Apple Inc. build 5664) (if
that matters?) Out of my depth here.
On Fri, May 6, 2011 at 5:07 PM, Nicolas Frisby
For this vanilla program
module Main where
main = print $ fib 40
fib 0 = 1 fib 1 = 1 fib n = fib (n - 1) + fib (n - 2)
with these commands
$ ghc -prof -auto-all -rtsopts -O --make Main.hs -o Main $ ./Main +RTS -p
all of the %time cells in the generated Main.prof file are 0.0, as is the total time count (0.00 secs and 0 ticks). The %alloc cells seem normal.
Andy Gill noticed that if you compile with -threaded, the %time cells seem normal.
I scanned the GHC Trac tickets specific to Mac OS X, but saw no titles that looked similar. Is this a known issue?
Thanks.

On 6 May 2011, at 23:07, Nicolas Frisby wrote:
all of the %time cells in the generated Main.prof file are 0.0, as is the total time count (0.00 secs and 0 ticks). The %alloc cells seem normal.
See http://hackage.haskell.org/trac/ghc/ticket/5137 Regards, Malcolm
participants (2)
-
Malcolm Wallace
-
Nicolas Frisby