Dictionaries and full laziness transformation

Akio Takano tkn.akio at gmail.com
Mon Feb 7 05:09:57 CET 2011


Hi,

I'm using GHC 7.0.1. I found that recursive overloaded functions tend
to leak memory when compiled with full-laziness optimization on. Here
is a simple case.

-- TestSub.hs
{-# LANGUAGE BangPatterns #-}
module TestSub where

{-# NOINLINE factorial #-}
factorial :: (Num a) => a -> a -> a
factorial !n !acc = if n == 0 then acc else factorial (n - 1) (acc * n)

-- main.hs
import TestSub

factorial1 :: Int -> Int -> Int
factorial1 = factorial

main = do
    n <- readLn
    print $ factorial1 n 1

    main

This program should run in constant space, and compiled with -O0 or
-O2 -fno-full-laziness, it does. However with -O2, it takes a linear
amount of memory. The core for factorial looks like this:

TestSub.factorial =
  \ (@ a_ajm) ($dNum_slz :: GHC.Num.Num a_ajm) ->
    let {
      a_slA :: GHC.Classes.Eq a_ajm
      [LclId]
      a_slA = GHC.Num.$p1Num @ a_ajm $dNum_slz } in
    let {
      lvl2_slC :: a_ajm -> a_ajm -> a_ajm
      [LclId]
      lvl2_slC = TestSub.factorial @ a_ajm $dNum_slz } in
...

The problem is that lvl2_slC closure is created whenever factorial is
applied to a Num dictionary, and kept alive until that application is
GCed. In this program it never happens, because an application to the
Num Int dictionary is referred to by the factorial1 CAF, and it
recursively keeps the whole chain of closures alive.

I know that full laziness transformation *sometimes* causes a space
leak, but this looks like a bad result to me, because:

- It looks like there is no point building a lot of equivalent
closures, instead of one.
- A lot of code can suffer from this behavior, because overloaded
recursive functions are fairly common.
  For example, unfoldConvStream function from the latest iteratee
package suffers from this problem, if I understand correctly.

Does anyone have an idea on whether this can be fixed in GHC, or how
to work around this problem?

Regards,

Takano Akio



More information about the Glasgow-haskell-users mailing list