Performance/Strictness
Haskell Performance Resource
Constructs: Techniques: |
Haskell is a non-strict language, and most implementations use a strategy called laziness to run your program. Basically laziness == non-strictness + sharing.
Laziness can be a useful tool for improving performance, but more often than not it reduces performance by adding a constant overhead to everything. Because of laziness, the compiler can't evaluate a function argument and pass the value to the function, it has to record the expression in the heap in a suspension (or thunk) in case it is evaluated later. Storing and evaluating suspensions is costly, and unnecessary if the expression was going to be evaluated anyway.
Strictness analysis[edit]
Optimising compilers like GHC try to reduce the cost of laziness using strictness analysis, which attempts to determine which function arguments are always evaluated by the function, and hence can be evaluated by the caller instead. Sometimes this leads to bigger gains; a strict Int
can be passed as an unboxed value, for example. Strictness analysis sometimes does wonderful things; for example it is very good at optimising fac
:
fac :: Int -> Int
fac n = if n <= 1 then 1 else n * fac (n-1)
Strictness analysis can spot the fact that the argument n
is strict, and can be represented unboxed. The resulting function won't use any heap while it is running, as you'd expect.
The common case of misunderstanding of strictness analysis is when folding (reducing) lists. If this program
main = print (foldl (+) 0 [1..1000000])
is compiled in GHC without "-O" flag, it uses a lot of heap and stack. A programmer knows that the long list ([1..1000000]
) is stored as a thunk, not fully, because the programmer read about non-strict semantics and lazy vs. non-strict. The programmer explicitly wrote sum
as tail recursive, so the program should use a small amount of stack, because the programmer knows about stack overflow. So behavior of the program looks mysterious to the programmer.
The programmer concludes that the program somehow decides to store the long list fully in the heap, or garbage collector is not able to remove dead prefix of the long list. Wrong. The long list is fine.
Look at the definition from the standard library.
foldl :: (a -> b -> a) -> a -> [b] -> a
foldl f z0 xs0 = lgo z0 xs0
where
lgo z [] = z
lgo z (x:xs) = lgo (f z x) xs
lgo
, instead of adding elements of the long list, creates a thunk for (f z x)
. z
is stored within that thunk, and z
is a thunk also, created during the previous call to lgo
. The program creates the long chain of thunks. Stack is bloated when evaluating that chain.
With "-O" flag GHC performs strictness analysis, then it knows that lgo
is strict in z
argument, therefore thunks are not needed and are not created.
Limitations of strictness analysis[edit]
It's easy to accidentally write functions that aren't strict, though. Often a lazy function can be sitting around eating up your performance, when making it strict wouldn't change the meaning of the program. For example:
suminit :: [Int] -> Int -> Int -> (Int,[Int])
suminit xs len acc = case len == 0 of
True -> (acc,xs)
False -> case xs of
[] -> (acc,[])
x:xs -> suminit xs (len-1) (acc+x)
main = print (fst (suminit [1..] 1000000 0))
this function sums the first len
elements of a list, returning the sum and the remaining list. We've already tried to improve performance by using an accumulating parameter. However, the parameter acc
isn't strict, because there's no guarantee that the caller will evaluate it. The compiler will use a fully boxed Int
to represent acc
, although it will probably use an unboxed Int
to represent len
. The expression (acc+x)
will be saved as a suspension, rather than evaluated on the spot. (Incidentally, this is a common pattern we see crop up time and again in small recursive functions with a few parameters).
Explicit strictness[edit]
We can make an argument strict explicitly.
In the foldl
example, replace foldl
with foldl'
.
For suminit
, we need to make acc
strict. The way to do this is using seq
:
suminit :: [Int] -> Int -> Int -> (Int,[Int])
suminit xs len acc = acc `seq` case len == 0 of
True -> (acc,xs)
False -> case xs of
[] -> (acc,[])
x:xs -> suminit xs (len-1) (acc+x)
Some other languages (eg. Clean) have strictness annotations on types, which is a less ugly way to express this, but for now there are no Haskell compilers that support this.
With the BangPatterns GHC extension enabled, the above can be written as
∗ For strict data structures, see Performance/Data_types.
suminit xs !len !acc = …
Incidentally, GHC will also eliminate the tuple returned by this function if the caller immediately deconstructs it.
Evaluating expressions strictly[edit]
There's a useful variant of the infix application operator ($)
that evaluates its argument strictly: ($!)
. This can often be used to great effect in eliminating unnecessary suspensions that the compiler hasn't spotted. eg. in a function application
f (g x)
writing instead
f $! (g x)
will be more efficient if (a) you were going to evaluate (g x)
anyway, and (b) f
isn't visibly strict, or inlined. If f
is strict or inlined, then the chances are that ($!)
is unnecessary cruft here.
A good example is the monadic return. If you find yourself writing
do …
…
return (fn x)
then consider instead writing
do …
…
return $! fn x
it is very rare to actually need laziness in the argument of return here.
Warning: Using any kind of strictness annotations as above can have unexpected impact on program semantics, in particular when certain optimizations are performed by the compiler. See correctness of short cut fusion.
Rule of Thumb for Strictness Annotation[edit]
A rule of thumb for when strictness annotation might be needed:
When a function f
with argument x
satisfies both conditions:
f
calls a function on a function ofx
:(h (g x))
- is not already strict in
x
(does not inspectx
's value),
then it can be helpful to force evaluation:
Example:
-- Force Strict: Make g's argument smaller.
f x = g $! (h x)
-- Don't force: f isn't building on x, so just let g deal with it.
f x = g x
-- Don't force: f is already strict in x
f x = case x of
0 -> (h (g x))