I found that the runtime stats output was incorrect for the one-line stats
(i.e. the +RTS -t -RTS output). The output was giving zeros for several of the
times, for example the mutator time. The problem was that the time values were
being computed inside a conditional so they were not correctly set for the
one-line outputs, but they were set for the more verbose outputs (i.e. -s).

I wrote a small patch that fixes the problem by moving the computation outside
of the conditional. The patch is available on the stats-fix branch here:

    git://github.com/dmpots/ghc.git stats-fix

Unfortunately I am unable to validate, because the validate script fails even 
without my patch. It gives this error:

compiler/nativeGen/AsmCodeGen.lhs:71:1:
    Warning: The import of `Config' is redundant
               except perhaps to import instances from `Config'
             To import instances alone, use: import Config()

<no location info>: 
Failing due to -Werror.


For those interested, here is a small example that shows the problem.

    $ cat Main.hs 

    module Main where
    import System.Environment

    loop 0 n = putStrLn $ "Done: " ++ n
    loop m n = loop (m-1) n

    main = do
      [n] <- getArgs
      loop (read n) n

In the head version, notice that the mutator time is zero (0.0 MUT).

    $ time ./head 20000000 +RTS -tstderr  -RTS
    Done: 20000000
    <<ghc: 3200064664 bytes, 6111 GCs, 2088/2088 avg/max bytes residency (1 
samples), 1M in use, 0.00 INIT (0.00 elapsed), 0.00 MUT (0.00 elapsed), 0.06 GC 
(0.08 elapsed) :ghc>>

    real        0m4.202s
    user        0m4.162s
    sys 0m0.037s

In the fixed version, it looks correct (4.90 MUT).

    $ time ./fixed 20000000 +RTS -tstderr  -RTS
    Done: 20000000
    <<ghc: 3200064664 bytes, 6111 GCs, 2088/2088 avg/max bytes residency (1 
samples), 1M in use, 0.00 INIT (0.00 elapsed), 4.90 MUT (4.94 elapsed), 0.08 GC 
(0.09 elapsed) :ghc>>

    real        0m5.041s
    user        0m4.981s
    sys 0m0.050s

_______________________________________________
Cvs-ghc mailing list
Cvs-ghc@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to