At 14:29 +0200 1999/06/05, Juan Jose Garcia Ripoll wrote:
>can anybody point me to tutorials, papers, etc, on how to properly
>annotate strictness in Haskell code? I am concerned with the following
>stupid piece of code that eats a lot of memory and takes an incredible
>amount of time to produce some output. I hope somebody will help me in
>finding what I am doing wrong.

One way to analyze it is to use the Heap Profiler version of Hugs:

>module Main where
>
>import Array
>
>produce :: Int -> Double -> Array Int Double
>produce n x = array (1,n) [(i,x) | i <- [1..n]]
>
>scprod :: Array Int Double -> Array Int Double -> Double
>scprod a b =
>        case (bounds a, bounds b) of
>          ((1,i), (1,j)) ->
>                foldl (+) start [a!(x) * b!(x) | x <- [2..i]]
>                where start = a!(1) * b!(1)
>
>main = print (show (scprod a a))
>       where a = produce 1000000 1.0

I ran your program with the modification
    main = print (show (scprod a a))
           where a = produce 1000 1.0
The Heap Profiler is very slow and consumes a lot of memory, so try it only
on small values.

The Heap Profiler produces an output that can be put through a program
hp2ps which translates it to PS. I further used GhostScript (or GhostView)
to convert PS -> PDF.

It then reveals that your program has two phases, the first in which
produce() consumes a lot of heap, and a second phase in which foldl() but
mainly scprod() consumes a lot of heap.

So I gather these are the spots you should try to optimize. Then use the
heap profiler again to see if you succeeded.

In fact your program is a very good example on how the Heap Profiler can be
used.

  Hans Aberg
                  * Email: Hans Aberg <mailto:[EMAIL PROTECTED]>
                  * Home Page: <http://www.matematik.su.se/~haberg/>
                  * AMS member listing: <http://www.ams.org/cml/>




Reply via email to