It should be accurate.  Hard to say more without investigating your
program in detail.

Try -ddump-simpl (with your profiling flags) to see how your function
looks just before code generation.

Simoin

| -----Original Message-----
| From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED]
| On Behalf Of Hal Daume
| Sent: 09 July 2003 23:17
| To: [EMAIL PROTECTED]
| Subject: how much can %alloc in profiling be trusted
| 
| In my program, I get the following time/allocation information for a
| call to my cosine function:
| 
|                              individual      inherited
| COST CENTRE   no. entries  %time  %alloc  %time  %alloc
| cosine               2721  43.1   74.3    43.1   74.3
| 
| this is a shocking amount of allocation, considering the definition of
| the function:
| 
| cosine :: Vector -> Vector -> Double
| cosine v1 v2 =
|   case dot v1 v2 0 of
|     n | n <= 0    -> 0
|       | otherwise -> n / (size v1 * size v2)
|   where
|     dot [] _  n = n
|     dot _  [] n = n
|     dot ((x,xv):xs) ((y,yv):ys) n =
|       case x `compare` y of
|         EQ -> dot xs ys $! (xv * yv + n)
|         LT -> dot xs ((y,yv):ys) n
|         GT -> dot ((x,xv):xs) ys n
| --    size = sqrt . sum . map (square . snd)
|     size l = sqrt $! size' l 0
|     size' [] n = n
|     size' ((_,x):xs) n = size' xs $! n + x*x
| 
| where Vector = [(Int,Double)] is a sparse vector representation.  This
| was even higher (moderately) until I switched from the old to the new
| definition of size listed there.
| 
| You can't blame this on the fact that the two vectors are being passed
| lazily either: they're being read strictly from a file and even seq'd
| before being put into the list.  Specifically, we have (v0 is passed
in
| to the function from top-level):
| 
|   ... do
|     v <- readList_H h
|     return (cosine v0 v, w)
| 
| where readList_H is defined as:
| 
| readList_H h = do
|   b <- FastIO.isEOF h
|   c <- FastIO.fscanfChar h
|   if c /= ' '
|     then return []
|     else do
|       b <- FastIO.isEOF h
|       i <- FastIO.fscanfInt h
|       FastIO.fscanfChar h
|       v <- FastIO.fscanfFloat h
|       rest <- readList_H h
|       return ((force (force i,force $ floatToDouble v)) : rest)
|   where force x = x `seq` x
| 
| as far as i can tell, all the list allocation should be happening
here.
| (the forces were not there in the beginning -- I added them later but
it
| changed nothing.)
| 
|  - Hal
| 
| --
|  Hal Daume III                                   | [EMAIL PROTECTED]
|  "Arrest this man, he talks in maths."           | www.isi.edu/~hdaume
| _______________________________________________
| Glasgow-haskell-users mailing list
| [EMAIL PROTECTED]
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


_______________________________________________
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to