
All, I'm looking for advice on how to figure out why some piece of code is allocating memory when I think it ought to be able to work in constant space. In these cases we cannot turn on traditional profiling since that would interfere with the optimisations we are relying on to eliminate most of the other memory allocations. Would looking at the core files help? What would I be looking for? Here's a simple version that I would expect to run in constance space. pixbufSetGreen :: Pixbuf -> IO () pixbufSetGreen pixbuf = do ptr <- pixbufGetPixels pixbuf sequence_ [ do pokeByteOff ptr (y*384+3*x) (0 ::Word8) pokeByteOff ptr (y*384+3*x+1) (128::Word8) pokeByteOff ptr (y*384+3*x+2) (96 ::Word8) | y <- [0..127] , x <- [0..127] ] (Don't worry about all those random constants, it's just test code!) I thought this might be the case since in ghc's Data.Array.Base we have some similar style code: {-# INLINE newArray #-} -- The INLINE is crucial, because until we know at least which monad -- we are in, the code below allocates like crazy. So inline it, -- in the hope that the context will know the monad. newArray (l,u) init = do marr <- newArray_ (l,u) sequence_ [unsafeWrite marr i init | i <- [0 .. rangeSize (l,u) - 1]] return marr Note of course that in my example we know exactly which monad we're using. Here is the real example code I was writing when I found that it was using lots of cpu cycles and +RTS -B -RTS beeps lots and lots. Compiled using -O (-O2 is the same) -fglasgow-exts with ghc-6.2.2. pixbufSetPixelsRGB8 :: Pixbuf -> (Int -> Int -> (# Word8, Word8, Word8 #)) -> IO () pixbufSetPixelsRGB8 pixbuf setPixel = do -- TODO assert that the format is RGB8 rowStride <- pixbufGetRowstride pixbuf width <- pixbufGetWidth pixbuf height <- pixbufGetHeight pixbuf let loop ptr y | y == height = return () | otherwise = do let rowLoop ptr x | x == width = return () | otherwise = case setPixel x y of (# red, green, blue #) -> do pokeByteOff ptr 0 red pokeByteOff ptr 1 green pokeByteOff ptr 2 blue rowLoop (ptr `plusPtr` 3) (x+1) rowLoop ptr 0 loop (ptr `plusPtr` rowStride) (y+1) pixelsPtr <- pixbufGetPixels pixbuf loop pixelsPtr 0 It was being called like so: setWierdColour :: Int -> Pixbuf -> IO () setWierdColour counter pixbuf = let val = fromIntegral counter in pixbufSetPixelsRGB8 pixbuf (\x y -> (# fromIntegral x + val , fromIntegral y + val , fromIntegral x + fromIntegral y + val #)) Duncan

Duncan Coutts wrote:
All,
I'm looking for advice on how to figure out why some piece of code is allocating memory when I think it ought to be able to work in constant space.
In these cases we cannot turn on traditional profiling since that would interfere with the optimisations we are relying on to eliminate most of the other memory allocations.
I don't understand why you can't use profiling as a debugging tool. How would profileing, ifor test purposes, cause other things to break? <snip>
Duncan
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
!DSPAM:4200ddb972401401013949!

On Wed, 2005-02-02 at 13:30 -0700, Seth Kurtzberg wrote:
Duncan Coutts wrote:
In these cases we cannot turn on traditional profiling since that would interfere with the optimisations we are relying on to eliminate most of the other memory allocations.
I don't understand why you can't use profiling as a debugging tool. How would profileing, ifor test purposes, cause other things to break?
The problem is that profiling add in extra parameters and extra code to each function (each SCC). This can interfere with optimisations like inlining and unboxing I believe. Simon could explain it better. Generally profiling is great, but for some of these low level optimisation problems you can end up profiling a different program program to the one you are interested in (the unoptimised one rather than the optimised one). Duncan

Duncan Coutts wrote:
On Wed, 2005-02-02 at 13:30 -0700, Seth Kurtzberg wrote:
Duncan Coutts wrote:
In these cases we cannot turn on traditional profiling since that would interfere with the optimisations we are relying on to eliminate most of the other memory allocations.
I don't understand why you can't use profiling as a debugging tool. How would profileing, ifor test purposes, cause other things to break?
The problem is that profiling add in extra parameters and extra code to each function (each SCC). This can interfere with optimisations like inlining and unboxing I believe. Simon could explain it better.
Generally profiling is great, but for some of these low level optimisation problems you can end up profiling a different program program to the one you are interested in (the unoptimised one rather than the optimised one).
Yes, I can see that. I've had problems in other languages where using the debugger stopped a seg fault. Obviously not the same situation, but a similar problem. Have you come up with a solution?
Duncan
!DSPAM:420176b7116488359410460!
participants (2)
-
Duncan Coutts
-
Seth Kurtzberg