[Haskell-cafe] Question about memory usage

John van Groningen johnvg at cs.ru.nl
Wed Aug 18 06:45:00 EDT 2010


Sebastian Fischer wrote:
>>BTW, what sort of memory usage are we talking about here?
>
>I was referring to the memory usage of this program
>
>    import System.Environment
>    import Data.Numbers.Fibonacci
>
>    main :: IO ()
>    main = do n <- (read . head) `fmap` getArgs
>              (fib n :: Integer) `seq` return ()
>
>compiled with -O2 and run with +RTS -s:
>
>    ./calcfib 100000000 +RTS -s
>         451,876,020 bytes allocated in the heap
>              10,376 bytes copied during GC
>          19,530,184 bytes maximum residency (9 sample(s))
>          12,193,760 bytes maximum slop
>                  97 MB total memory in use (6 MB lost due to fragmentation)
>
>      Generation 0:    40 collections,     0 parallel,  0.00s,  0.00s elapsed
>      Generation 1:     9 collections,     0 parallel,  0.00s,  0.00s elapsed
>
>      INIT  time    0.00s  (  0.00s elapsed)
>      MUT   time   12.47s  ( 13.12s elapsed)
>      GC    time    0.00s  (  0.00s elapsed)
>      EXIT  time    0.00s  (  0.00s elapsed)
>      Total time   12.47s  ( 13.13s elapsed)
>
>      %GC time       0.0%  (0.0% elapsed)
>
>      Alloc rate    36,242,279 bytes per MUT second
>
>      Productivity 100.0% of total user, 95.0% of total elapsed
>..

You could try:

fibo :: Int -> Integer
fibo n
  = if n<=1 then fromIntegral n else
      if even n
         then let (f_nd2m1,f_nd2) = dfibo (n `quot` 2-1) in f_nd2 * (f_nd2 + (f_nd2m1+f_nd2m1))
         else let (f_nd2,f_nd2p1) = dfibo (n `quot` 2)   in f_nd2*f_nd2 + f_nd2p1*f_nd2p1
  where
    dfibo :: Int -> (Integer,Integer)
    dfibo n
      = if n<=1 then (fromIntegral n,1) else
          let (f_nd2,f_nd2p1) = dfibo (n `quot` 2) in
            if even n
              then let f_n = (f_nd2p1 + (f_nd2p1-f_nd2)) * f_nd2
                       f_np1 = f_nd2*f_nd2 + f_nd2p1*f_nd2p1
                   in  seq f_n (seq f_np1 (f_n,f_np1))
              else let f_n = f_nd2*f_nd2 + f_nd2p1*f_nd2p1
                       f_np1 = f_nd2p1 * (f_nd2p1 + (f_nd2+f_nd2))
                   in  seq f_n (seq f_np1 (f_n,f_np1))

It allocates less and has a smaller maximum residency: (ghc 6.12.2,windows 7 64)

     292,381,520 bytes allocated in the heap
          15,200 bytes copied during GC
      13,020,308 bytes maximum residency (8 sample(s))
       6,423,332 bytes maximum slop
              99 MB total memory in use (9 MB lost due to fragmentation)


  Generation 0:    29 collections,     0 parallel,  0.00s,  0.00s elapsed
  Generation 1:     8 collections,     0 parallel,  0.00s,  0.00s elapsed

  INIT  time    0.00s  (  0.02s elapsed)
  MUT   time    5.85s  (  5.88s elapsed)
  GC    time    0.00s  (  0.00s elapsed)
  EXIT  time    0.00s  (  0.00s elapsed)
  Total time    5.85s  (  5.90s elapsed)

  %GC time       0.0%  (0.0% elapsed)

  Alloc rate    49,979,430 bytes per MUT second

  Productivity 100.0% of total user, 99.2% of total elapsed

instead of:

    451,864,588 bytes allocated in the heap
           8,600 bytes copied during GC
      17,362,424 bytes maximum residency (8 sample(s))
      11,332,592 bytes maximum slop
              99 MB total memory in use (9 MB lost due to fragmentation)

  Generation 0:    41 collections,     0 parallel,  0.00s,  0.00s elapsed
  Generation 1:     8 collections,     0 parallel,  0.00s,  0.00s elapsed

  INIT  time    0.00s  (  0.02s elapsed)
  MUT   time    9.11s  (  9.14s elapsed)
  GC    time    0.00s  (  0.00s elapsed)
  EXIT  time    0.00s  (  0.00s elapsed)
  Total time    9.11s  (  9.16s elapsed)

  %GC time       0.0%  (0.0% elapsed)

  Alloc rate    49,598,449 bytes per MUT second

  Productivity 100.0% of total user, 99.5% of total elapsed

Kind regards.

John van Groningen


More information about the Haskell-Cafe mailing list