Difference between revisions of "Performance/GHC"

From HaskellWiki
Jump to navigation Jump to search
m (→‎Looking at the Core: Direct link to the paper)
m (→‎Summary: Fix formatting)
Line 335: Line 335:
 
=== Summary ===
 
=== Summary ===
   
* Manually inspect the Core that is generated
+
* Manually inspect the Core that is generated
* Use strictness annotations to ensure loops are unboxed
+
* Use strictness annotations to ensure loops are unboxed
* Watch out for optimisations such as CSE and strength reduction that are missed
+
* Watch out for optimisations such as CSE and strength reduction that are missed
* Read the generated C for really tight loops.
+
* Read the generated C for really tight loops.
* Use -fexcess-precision and -optc-ffast-math for doubles
+
* Use -fexcess-precision and -optc-ffast-math for doubles

Revision as of 01:50, 17 February 2006

Haskell Performance Resource

Constructs:
Data Types - Functions
Overloading - FFI - Arrays
Strings - Integers - I/O
Floating point - Concurrency
Modules - Monads

Techniques:
Strictness - Laziness
Avoiding space leaks
Accumulating parameter

Implementation-Specific:
GHC - nhc98 - Hugs
Yhc - JHC

Please report any overly-slow GHC-compiled programs. Since GHC doesn't have any credible competition in the performance department these days it's hard to say what overly-slow means, so just use your judgement! Of course, if a GHC compiled program runs slower than the same program compiled by another compiler, then it's definitely a bug.

Use Optimisation

Optimise, using -O or -O2: this is the most basic way to make your program go faster. Compilation time will be slower, especially with -O2.

At present, -O2 is nearly indistinguishable from -O.

GHCi cannot optimise interpreted code, so when using GHCi, compile critical modules using -O or -O2, then load them into GHCi.

Measuring Performance

The first thing to do is measure the performance of your program, and find out whether all the time is being spent in the garbage collector or not. Run your program with the +RTS -sstderr option:

$ ./clausify 20 +RTS -sstderr
42,764,972 bytes allocated in the heap
 6,915,348 bytes copied during GC (scavenged)
   360,448 bytes copied during GC (not scavenged)
    36,616 bytes maximum residency (7 sample(s))
        81 collections in generation 0 (  0.07s)
         7 collections in generation 1 (  0.00s)
         2 Mb total memory in use
 INIT  time    0.00s  (  0.00s elapsed)
 MUT   time    0.65s  (  0.94s elapsed)
 GC    time    0.07s  (  0.06s elapsed)
 EXIT  time    0.00s  (  0.00s elapsed)
 Total time    0.72s  (  1.00s elapsed)
 %GC time       9.7%  (6.0% elapsed)
 Alloc rate    65,792,264 bytes per MUT second
 Productivity  90.3% of total user, 65.1% of total elapsed

This tells you how much time is being spent running the program itself (MUT time), and how much time spent in the garbage collector (GC time).

If your program is doing a lot of GC, then your first priority should be to check for Space Leaks using heap profiling, and then to try to reduce allocations by time and allocation profiling.

If you can't reduce the GC cost any further, then using more memory by tweaking the GC options will probably help. For example, increasing the default heap size with +RTS -H128m will reduce the number of GCs.

If your program isn't doing too much GC, then you should proceed to time and allocation profiling to see where the big hitters are.

Unboxed types

When you are really desperate for speed, and you want to get right down to the “raw bits.” Please see GHC Primitives for some information about using unboxed types.

This should be a last resort, however, since unboxed types and primitives are non-portable. Fortunately, it is usually not necessary to resort to using explicit unboxed types and primitives, because GHC's optimiser can do the work for you by inlining operations it knows about, and unboxing strict function arguments (see Performance:Strictness). Strict and unpacked constructor fields can also help a lot (see Performance:Data Types). Sometimes GHC needs a little help to generate the right code, so you might have to look at the Core output to see whether your tweaks are actually having the desired effect.

One thing that can be said for using unboxed types and primitives is that you know you're writing efficient code, rather than relying on GHC's optimiser to do the right thing, and being at the mercy of changes in GHC's optimiser down the line. This may well be important to you, in which case go for it.


Looking at the Core

GHC's compiler intermediate language can be very useful for improving the performance of your code. Core is a functional language much like a very stripped down Haskell (by design), so it's still readable, and still purely functional. The general technique is to iteratively inspect how the critical functions of your program are compiled to Core, checking that they're compiled in the most optimal manner. Sometimes GHC doesn't quite manage to unbox your function arguments, float out common subexpressions, or unfold loops ideally -- but you'll only know if you read the Core.

References:

Core by Example

Here's a step-by-step guide to optimising a particular program, the partial-sums problem from the Great Language Shootout. We developed a number of examples on Haskell shootout entry page.

Begin with the naive translation of the Clean entry (which was fairly quick): Lots of math in a tight loop.

import System
import Numeric
main = do n <- getArgs = readIO . head
          let sums     = loop 1 n 1 0 0 0 0 0 0 0 0 0
              fn (s,t) = putStrLn $ (showFFloat (Just 9) s []) ++ "\t" ++ t
          mapM_ (fn :: (Double, String) - IO ()) (zip sums names)
names = ["(2/3)^k", "k^-0.5", "1/k(k+1)", "Flint Hills", "Cookson Hills"
        , "Harmonic", "Riemann Zeta", "Alternating Harmonic", "Gregory"]
loop k n alt a1 a2 a3 a4 a5 a6 a7 a8 a9
    | k  n     = [ a1, a2, a3, a4, a5, a6, a7, a8, a9 ]
    | otherwise = loop (k+1) n (-alt)
                       (a1 + (2/3) ** (k-1))
                       (a2 + k ** (-0.5))
                       (a3 + 1 / (k * (k + 1)))
                       (a4 + 1 / (k*k*k * sin k * sin k))
                       (a5 + 1 / (k*k*k * cos k * cos k))
                       (a6 + 1 / k)
                       (a7 + 1 / (k*k))
                       (a8 + alt / k)
                       (a9 + alt / (2 * k - 1))

Compiled with -O2 it runs. However, the performance is really bad. Somewhere greater than 128M heap -- in fact eventually running out of memory. A classic space leak. So look at the generated Core.

Inspect the Core

The best way to check the Core that GHC generates is with the -ddump-simpl flag (dump the results after code simplification, and after all optimisations are run). The result can be verbose, so pipe it into a pager.

Looking for the 'loop', we find that it has been compiled to a function with the following type:

$sloop_r2U6 :: GHC.Prim.Double#
               -> GHC.Float.Double
               -> GHC.Float.Double
               -> GHC.Float.Double
               -> GHC.Float.Double
               -> GHC.Float.Double
               -> GHC.Float.Double
               -> GHC.Float.Double
               -> GHC.Float.Double
               -> GHC.Float.Double
               -> GHC.Float.Double
               -> GHC.Prim.Double#
               -> [GHC.Float.Double]

Hmm, I certainly don't want boxed doubles in such a tight loop (boxed values are represented as pointers to closures on the heap, unboxed values are raw machine values).

Strictify

The next step then is to encourage GHC to unbox this loop, by providing some strictness annotations. So rewrite the loop like this:

loop k n alt a1 a2 a3 a4 a5 a6 a7 a8 a9
    | () !k !n !alt !a1 !a2 !a3 !a4 !a5 !a6 !a7 !a8 !a9 !False = undefined
    | k > n     = [ a1, a2, a3, a4, a5, a6, a7, a8, a9 ]
    | otherwise = loop (k+1) n (-alt)
                       (a1 + (2/3) ** (k-1))
                       (a2 + k ** (-0.5))
                       (a3 + 1 / (k * (k + 1)))
                       (a4 + 1 / (k*k*k * sin k * sin k))
                       (a5 + 1 / (k*k*k * cos k * cos k))
                       (a6 + 1 / k)
                       (a7 + 1 / (k*k))
                       (a8 + alt / k)
                       (a9 + alt / (2 * k - 1)) where x ! y = x `seq` y

Here the first guard is purely a syntactic trick to inform ghc that the arguments should be strictly evaluated. I've played a little game here, using ! for `seq` is reminiscent of the new bang-pattern proposal for strictness. Let's see how this compiles. Strictifying all args GHC produces an inner loop of:

$sloop_r2WS :: GHC.Prim.Double#
               -> GHC.Prim.Double#
               -> GHC.Prim.Double#
               -> GHC.Prim.Double#
               -> GHC.Prim.Double#
               -> GHC.Prim.Double#
               -> GHC.Prim.Double#
               -> GHC.Prim.Double#
               -> GHC.Prim.Double#
               -> GHC.Prim.Double#
               -> GHC.Prim.Double#
               -> GHC.Prim.Double#
               -> [GHC.Float.Double]

Ah! perfect. Let's see how that runs:

$ ghc Naive.hs -O2 -no-recomp
$ time ./a.out 2500000
3.000000000     (2/3)^k
3160.817621887  k^-0.5
0.999999600     1/k(k+1)
30.314541510    Flint Hills
42.995233998    Cookson Hills
15.309017155    Harmonic
1.644933667     Riemann Zeta
0.693146981     Alternating Harmonic
0.785398063     Gregory
./a.out 2500000  4.45s user 0.02s system 99% cpu 4.482 total

Crank up the gcc flags

Not too bad. No space leak and quite zippy. But let's see what more can be done. First, double arithmetic usually (always?) benefits from -fexcess-precision, and cranking up the flags to gcc:

paprika$ ghc Naive.hs -O2 -fexcess-precision -optc-O3 -optc-ffast-math -no-recomp
paprika$ time ./a.out 2500000
3.000000000     (2/3)^k
3160.817621887  k^-0.5
0.999999600     1/k(k+1)
30.314541510    Flint Hills
42.995233998    Cookson Hills
15.309017155    Harmonic
1.644933667     Riemann Zeta
0.693146981     Alternating Harmonic
0.785398063     Gregory
./a.out 2500000  3.71s user 0.01s system 99% cpu 3.726 total

Even better! Now, let's dive into the Core to see if there are any optimisation opportunites that GHC missed. So add -ddump-simpl and peruse the output.

Common subexpressions

Looking at the Core, I see firstly that some of the common subexpressions haven't been factored out:

case [GHC.Float.Double] GHC.Prim./## 1.0
  (GHC.Prim.*## (GHC.Prim.*##
                    (GHC.Prim.*## (GHC.Prim.*## sc10_s2VS sc10_s2VS) sc10_s2VS)
                    (GHC.Prim.sinDouble# sc10_s2VS))
                 (GHC.Prim.sinDouble# sc10_s2VS))

Multiple calls to sin. Hmm... And similar for cos and k*k. Simon Peyton-Jones says:

GHC doesn't do full CSE.  It'd be a relatively easy pass for someone to
add, but it can cause space leaks.  And it can replace two
strictly-evaluated calls with one lazy thunk:
        let { x = case e of ....;  y = case e of .... } in ...
  ==>
        let { v = e; x = case v of ...; y = case v of ... } in ...
Instead GHC does "opportunistic CSE".  If you have
        let x = e in .... let y = e in ....
then it'll discard the duplicate binding. But that's very weak.

So it looks like we might have to float out the commmon subexpressions by hand. The inner loop now looks like:

loop k n alt a1 a2 a3 a4 a5 a6 a7 a8 a9
    | () !k !n !alt !a1 !a2 !a3 !a4 !a5 !a6 !a7 !a8 !a9 !False = undefined
    | k > n     = [ a1, a2, a3, a4, a5, a6, a7, a8, a9 ]
    | otherwise = loop (k+1) n (-alt)
                       (a1 + (2/3) ** (k-1))
                       (a2 + k ** (-0.5))
                       (a3 + 1 / (k * (k + 1)))
                       (a4 + 1 / (k3 * sk * sk))
                       (a5 + 1 / (k3 * ck * ck))
                       (a6 + 1 / k)
                       (a7 + 1 / k2)
                       (a8 + alt / k)
                       (a9 + alt / (2 * k - 1))
    where sk = sin k
          ck = cos k
          k2 = k * k
          k3 = k2 * k
          x ! y = x `seq` y

looking at the Core shows the sins are now allocated and shared:

let a9_s2MI :: GHC.Prim.Double#
    a9_s2MI = GHC.Prim.sinDouble# sc10_s2Xa

So the common expressions are floated out, and it now runs:

paprika$ time ./a.out 2500000                          
3160.817621887  k^-0.5
0.999999600     1/k(k+1)
30.314541510    Flint Hills
42.995233998    Cookson Hills
15.309017155    Harmonic
1.644933667     Riemann Zeta
0.693146981     Alternating Harmonic
0.785398063     Gregory
./a.out 2500000  3.29s user 0.00s system 99% cpu 3.290 total

Faster. So we gained 12% by floating out those common expressions.

Strength reduction

Finally, another trick -- manual strength reduction. When I checked the C entry, it used an integer for the k parameter to the loop, and cast it to a double for the math each time around, so perhaps we can make it an Int parameter. Secondly, the alt parameter only has it's sign flipped each time, so perhaps we can factor out the alt / k arg (it's either 1 / k or -1 on k), saving a division. Thirdly, (k ** (-0.5)) is just a slow way of doing a sqrt.

The final loop looks like:

loop i n alt a1 a2 a3 a4 a5 a6 a7 a8 a9
    | i !n !alt !a1 !a2 !a3 !a4 !a5 !a6 !a7 !a8 !a9 !False = undefined -- strict
    | k > n     = [ a1, a2, a3, a4, a5, a6, a7, a8, a9 ]
    | otherwise = loop (i+1) n (-alt)
                       (a1 + (2/3) ** (k-1))
                       (a2 + 1 / sqrt k)
                       (a3 + 1 / (k * (k + 1)))
                       (a4 + 1 / (k3 * sk * sk))
                       (a5 + 1 / (k3 * ck * ck))
                       (a6 + dk)
                       (a7 + 1 / k2)
                       (a8 + alt * dk)
                       (a9 + alt / (2 * k - 1))
    where k3 = k2*k; k2 = k*k; dk = 1/k; k = fromIntegral i :: Double
          sk = sin k; ck = cos k; x!y = x`seq`y

Checking the generated C code (for another tutorial, perhaps) shows that the same C operations are generated as the C entry uses.

And it runs:

$ time ./i 2500000
3.000000200     (2/3)^k
3186.765000000  k^-0.5
0.999852700     1/k(k+1)
30.314493000    Flint Hills
42.995068000    Cookson Hills
15.403683000    Harmonic
1.644725300     Riemann Zeta
0.693137470     Alternating Harmonic
0.785399100     Gregory
./i 2500000  2.37s user 0.01s system 99% cpu 2.389 total

A big speedup!

This entry in fact runs faster than hand optimised (and vectorised) GCC! And is only slower than optimised Fortran. Lesson: Haskell can be very, very fast.

So, by carefully tweaking things, we first squished a space leak, and then gained another 45%.

Summary

  • Manually inspect the Core that is generated
  • Use strictness annotations to ensure loops are unboxed
  • Watch out for optimisations such as CSE and strength reduction that are missed
  • Read the generated C for really tight loops.
  • Use -fexcess-precision and -optc-ffast-math for doubles