Go to the first, previous, next, last section, table of contents.

Faster: producing a program that runs quicker

The key tool to use in making your Haskell program run faster are GHC's profiling facilities, described separately in section See section Profiling Haskell programs. There is no substitute for finding where your program's time/space is really going, as opposed to where you imagine it is going.

Another point to bear in mind: By far the best way to improve a program's performance dramatically is to use better algorithms. Once profiling has thrown the spotlight on the guilty time-consumer(s), it may be better to re-think your program than to try all the tweaks listed below.

Another extremely efficient way to make your program snappy is to use library code that has been Seriously Tuned By Someone Else. You might be able to write a better quicksort than the one in the HBC library, but it will take you much longer than typing `import QSort'. (Incidentally, it doesn't hurt if the Someone Else is Lennart Augustsson.)

Please report any overly-slow GHC-compiled programs. The current definition of "overly-slow" is "the HBC-compiled version ran faster"...

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 version 0.26, `-O2' is nearly indistinguishable from `-O'.
Compile via C and crank up GCC:
Even with `-O', GHC tries to use a native-code generator, if available. But the native code-generator is designed to be quick, not mind-bogglingly clever. Better to let GCC have a go, as it tries much harder on register allocation, etc. So, when we want very fast code, we use: `-O -fvia-C -O2-for-C'.
Overloaded functions are not your friend:
Haskell's overloading (using type classes) is elegant, neat, etc., etc., but it is death to performance if left to linger in an inner loop. How can you squash it?
Give explicit type signatures:
Signatures are the basic trick; putting them on exported, top-level functions is good software-engineering practice, anyway. The automatic specialisation of overloaded functions should take care of overloaded local and/or unexported functions.
Use `SPECIALIZE' pragmas:
(UK spelling also accepted.) For key overloaded functions, you can create extra versions (NB: more code space) specialised to particular types. Thus, if you have an overloaded function:
hammeredLookup :: Ord key => [(key, value)] -> key -> value
If it is heavily used on lists with `Widget' keys, you could specialise it as follows:
{-# SPECIALIZE hammeredLookup :: [(Widget, value)] -> Widget -> value #-}
To get very fancy, you can also specify a named function to use for the specialised value, by adding `= blah', as in:
{-# SPECIALIZE hammeredLookup :: ...as before... = blah #-}
It's Your Responsibility to make sure that `blah' really behaves as a specialised version of `hammeredLookup'!!! An example in which the `= blah' form will Win Big:
toDouble :: Real a => a -> Double
toDouble = fromRational . toRational

{-# SPECIALIZE toDouble :: Int -> Double = i2d #-}
i2d (I# i) = D# (int2Double# i) -- uses Glasgow prim-op directly
The `i2d' function is virtually one machine instruction; the default conversion -- via an intermediate `Rational' -- is obscenely expensive by comparison. By using the US spelling, your `SPECIALIZE' pragma will work with HBC, too. Note that HBC doesn't support the `= blah' form. A `SPECIALIZE' pragma for a function can be put anywhere its type signature could be put.
Use `SPECIALIZE instance' pragmas:
Same idea, except for instance declarations. For example:
instance (Eq a) => Eq (Foo a) where { ... usual stuff ... }

{-# SPECIALIZE instance Eq (Foo [(Int, Bar)] #-}
Compatible with HBC, by the way. See also: overlapping instances, in Section See section "HBC-ish" extensions implemented by GHC. They are to `SPECIALIZE instance' pragmas what `= blah' hacks are to `SPECIALIZE' (value) pragmas...
"How do I know what's happening with specialisations?":
The `-fshow-specialisations' will show the specialisations that actually take place. The `-fshow-import-specs' will show the specialisations that GHC wished were available, but were not. You can add the relevant pragmas to your code if you wish. You're a bit stuck if the desired specialisation is of a Prelude function. If it's Really Important, you can just snap a copy of the Prelude code, rename it, and then SPECIALIZE that to your heart's content.
"But how do I know where overloading is creeping in?":
A low-tech way: grep (search) your interface files for overloaded type signatures; e.g.,:
% egrep '^[a-z].*::.*=>' *.hi
Note: explicit export lists sometimes "mask" overloaded top-level functions; i.e., you won't see anything about them in the interface file. I sometimes remove my export list temporarily, just to see what pops out.
Strict functions are your dear friends:
and, among other things, lazy pattern-matching is your enemy. (If you don't know what a "strict function" is, please consult a functional-programming textbook. A sentence or two of explanation here probably would not do much good.) Consider these two code fragments:
f (Wibble x y) =  ... # strict

f arg = let { (Wibble x y) = arg } in ... # lazy
The former will result in far better code. A less contrived example shows the use of `cases' instead of `lets' to get stricter code (a good thing):
f (Wibble x y)  # beautiful but slow
  = let
        (a1, b1, c1) = unpackFoo x
        (a2, b2, c2) = unpackFoo y
    in ...

f (Wibble x y)  # ugly, and proud of it
  = case (unpackFoo x) of { (a1, b1, c1) ->
    case (unpackFoo y) of { (a2, b2, c2) ->
    ...
    }}
GHC loves single-constructor data-types:
It's all the better if a function is strict in a single-constructor type (a type with only one data-constructor; for example, tuples are single-constructor types).
"How do I find out a function's strictness?"
Don't guess -- look it up. Look for your function in the interface file, then for the third field in the pragma; it should say `_S_ <string>'. The `<string>' gives the strictness of the function's arguments. `L' is lazy (bad), `S' and `E' are strict (good), `P' is "primitive" (good), `U(...)' is strict and "unpackable" (very good), and `A' is absent (very good). For an "unpackable" `U(...)' argument, the info inside tells the strictness of its components. So, if the argument is a pair, and it says `U(AU(LSS))', that means "the first component of the pair isn't used; the second component is itself unpackable, with three components (lazy in the first, strict in the second & third)." If the function isn't exported, just compile with the extra flag `-ddump-simpl'; next to the signature for any binder, it will print the self-same pragmatic information as would be put in an interface file. (Besides, Core syntax is fun to look at!)
Force key functions to be `INLINE'd (esp. monads):
GHC (with `-O', as always) tries to inline (or "unfold") functions/values that are "small enough," thus avoiding the call overhead and possibly exposing other more-wonderful optimisations. You will probably see these unfoldings (in Core syntax) in your interface files. Normally, if GHC decides a function is "too expensive" to inline, it will not do so, nor will it export that unfolding for other modules to use. The sledgehammer you can bring to bear is the `INLINE' pragma, used thusly:
key_function :: Int -> String -> (Bool, Double) 

#ifdef __GLASGOW_HASKELL__
{-# INLINE key_function #-}
#endif
(You don't need to do the C pre-processor carry-on unless you're going to stick the code through HBC -- it doesn't like `INLINE' pragmas.) The major effect of an `INLINE' pragma is to declare a function's "cost" to be very low. The normal unfolding machinery will then be very keen to inline it. An `INLINE' pragma for a function can be put anywhere its type signature could be put. `INLINE' pragmas are a particularly good idea for the `then'/`return' (or `bind'/`unit') functions in a monad. For example, in GHC's own `UniqueSupply' monad code, we have:
#ifdef __GLASGOW_HASKELL__
{-# INLINE thenUs #-}
{-# INLINE returnUs #-}
#endif
GHC reserves the right to disallow any unfolding, even if you explicitly asked for one. That's because a function's body may become unexportable, because it mentions a non-exported value, to which any importing module would have no access. If you want to see why candidate unfoldings are rejected, use the `-freport-disallowed-unfoldings' option.
Don't let GHC ignore pragmatic information:
Sort-of by definition, GHC is allowed to ignore pragmas in interfaces. Your program should still work, if not as well. Normally, GHC will ignore an unfolding pragma in an interface if it cannot figure out all the names mentioned in the unfolding. (A very much hairier implementation could make sure This Never Happens, but life is too short to wage constant battle with Haskell's module system.) If you want to prevent such ignorings, give GHC a `-fshow-pragma-name-errs' option. It will then treat any unresolved names in pragmas as errors, rather than inconveniences.
Explicit `export' list:
If you do not have an explicit export list in a module, GHC must assume that everything in that module will be exported. This has various pessimising effect. For example, if a bit of code is actually unused (perhaps because of unfolding effects), GHC will not be able to throw it away, because it is exported and some other module may be relying on its existence. GHC can be quite a bit more aggressive with pieces of code if it knows they are not exported.
Look at the Core syntax!
(The form in which GHC manipulates your code.) Just run your compilation with `-ddump-simpl' (don't forget the `-O'). If profiling has pointed the finger at particular functions, look at their Core code. `lets' are bad, `cases' are good, dictionaries (`d.<Class>.<Unique>') [or anything overloading-ish] are bad, nested lambdas are bad, explicit data constructors are good, primitive operations (e.g., `eqInt#') are good, ...
Use unboxed types (a GHC extension):
When you are really desperate for speed, and you want to get right down to the "raw bits." Please see section See section Unboxed types for some information about using unboxed types.
Use `_ccall_s' (a GHC extension) to plug into fast libraries:
This may take real work, but... There exist piles of massively-tuned library code, and the best thing is not to compete with it, but link with it. Section See section Calling C directly from Haskell says a little about how to use C calls.
Don't use `Float's:
We don't provide specialisations of Prelude functions for `Float' (but we do for `Double'). If you end up executing overloaded code, you will lose on performance, perhaps badly. `Floats' (probably 32-bits) are almost always a bad idea, anyway, unless you Really Know What You Are Doing. Use Doubles. There's rarely a speed disadvantage -- modern machines will use the same floating-point unit for both. With `Doubles', you are much less likely to hang yourself with numerical errors.
Use a bigger heap!
If your program's GC stats (`-S' RTS option) indicate that it's doing lots of garbage-collection (say, more than 20% of execution time), more memory might help -- with the `-H<size>' RTS option.
Use a smaller heap!
Some programs with a very small heap residency (toy programs, usually) actually benefit from running the heap size way down. The `-H<size>' RTS option, as above.
Use a smaller "allocation area":
If you can get the garbage-collector's youngest generation to fit entirely in your machine's cache, it may make quite a difference. The effect is very machine dependent. But, for example, a `+RTS -A128k' option on one of our DEC Alphas was worth an immediate 5% performance boost.


Go to the first, previous, next, last section, table of contents.