Profiling and analysing space usage

Alistair Bayley abayley at gmail.com
Thu Sep 1 10:36:09 EDT 2005


Hello all.

Below is a (typically pointless) program, which is a small slice from
a larger one I'm profiling. I'm interested in getting the memory usage
as small as possible. The loop function (and its analogue in the real
program) contributes significantly to the allocation stats. AFAICT,
this would be mainly due to a closure built for the if-stmt.

The heap profile graph for this program shows an initial peak, and
then the graph is flat at 8Mbytes, which I think is the space
allocated to the two STArrays (2 arrays, 1 million chars each, 4 bytes
per char?). So it looks as though any allocation for the loop function
is GC'd very soon after it's allocated.

So my questions are:

 - is my analysis of the space usage correct i.e. allocation in the
loop function is very short-lived and nothing to worry about?

 - is there anything I can do to reduce the memory usage, or is it
already minimal, assuming that I'm happy with the size of the
STArrays? I realise I could use, say, PackedStrings, but the original
program works on lists of (Eq a); I've just chosen Chars for this
example so as to eliminate polymorphism from the profiling.

Notes:
 - exporting only main makes a *big* difference to both space and time
usage, as does adding type signatures, to eliminate polymophism.


This is the only retainer set shown on the profiling graph:
SET 2 = {<MAIN.SYSTEM>}


COST CENTRE                    MODULE               %time %alloc

loop                           Main                  35.1   15.4
alloc_b                        Main                  19.5    7.7
main                           Main                  13.0   30.8
makeArray1                     Main                   9.1    5.1
loop_if                        Main                   9.1   41.0
inBounds                       Main                   6.5    0.0
test1M                         Main                   3.9    0.0
alloc_a                        Main                   3.9    0.0


module Main (main) where

import Data.Array.ST
import Control.Monad.ST

main :: IO ()
main = do
  let
    src = take 1000000 (repeat 'a')
    dst = take 1000000 (repeat 'a')
    d :: Int
    d = test1 src dst
  print d

test1 :: String -> String -> Int
test1 src dst = runST (test1M src dst)

test1M :: String -> String -> ST s Int
test1M src dst = do
  srca <- makeArray1 (length src) src
  dsta <- makeArray1 (length dst) dst
  loop srca dsta 1

inBounds :: STArray s Int Char -> Int -> Bool
inBounds arr i = case bounds arr of (l, u) -> i >= l && i <= u

makeArray1 :: Int -> [Char] -> ST s (STArray s Int Char)
makeArray1 len str = newListArray (1, len) str

loop :: STArray s Int Char -> STArray s Int Char -> Int -> ST s Int
loop srca dsta n = do
  if (inBounds srca n) && (inBounds dsta n)
    then do
      a <- {-# SCC "alloc_a" #-} readArray srca n
      b <- {-# SCC "alloc_b" #-} readArray dsta n
      {-# SCC "loop_if" #-} if a == b then (loop srca dsta (n+1)) else
(return n)
    else return n


More information about the Glasgow-haskell-users mailing list