On Wed, Mar 26, 2008 at 02:33:20PM -0700, Jim Snow wrote:
> 
> -Memory consumption is atrocious: 146 megs to render a scene that's a 
> 33k ascii file.  Where does it all go?  A heap profile reports the max 
> heap size at a rather more reasonable 500k or so.  (My architecture is 
> 64 bit ubuntu on a dual-core amd.)

I haven't looked properly yet, but it looks like something is leaking
memory that shouldn't be. The attached Gloom.hs uses constant memory,
but if you replace the "map" with the commented out "(parMap rnf)" then
the memory use seems to keep increasing, even once it has run display
once and is running it a second or third time.


Thanks
Ian

import Vec
import Clr
import Solid
import Trace
import Spd
import Control.Parallel.Strategies
import Data.Time.Clock.POSIX
import IO

get_color :: Flt -> Flt -> Scene -> Clr.Color
get_color x y scn =
 let (Scene sld lights (Camera pos fwd up right) dtex bgcolor) = scn
     dir = vnorm $ vadd3 fwd (vscale right (-x)) (vscale up y)
     ray = Ray pos dir
 in
  Trace.trace scn ray infinity 3

seqPixel :: (Float,Float,Float,Float,Float) -> ()
seqPixel (f1, f2, f3, f4, f5)
 = f1 `seq` f2 `seq` f3 `seq` f4 `seq` f5 `seq` ()

seqList' :: (a -> ()) -> [a] -> ()
seqList' _ [] = ()
seqList' f (x : xs) = f x `seq` seqList' f xs

gen_pixel_list :: Flt -> Flt -> Flt -> Flt -> Flt -> Flt -> Scene
               -> [(Float,Float,Float,Float,Float)]
gen_pixel_list curx cury stopx stopy maxx maxy scene =
 [ let scx = (x - midx) / midx
       scy = (y - midy) / midy
       Clr.Color r g b = get_color scx (scy * (midy / midx)) scene
   in (scx, scy, r, g, b)
 | x <- [curx .. (stopx - 1)],
   y <- [cury .. (stopy - 1)]
 ]
    where midx = maxx / 2
          midy = maxy / 2

gen_blocks_list :: Flt -> Flt -> Flt -> Scene -> IO ()
gen_blocks_list maxx maxy block_size scene =
 let xblocks = maxx / block_size
     yblocks = maxy / block_size
     blocks  = [ (x*block_size, y*block_size)
               | x <- [0..xblocks-1],
                 y <- [0..yblocks-1] ]
     pixels  = map -- (parMap rnf)
               (\(x,y) -> gen_pixel_list x y (x+block_size) (y+block_size) maxx maxy scene)
               blocks
 in
  do
   print ('A', xblocks)
   print ('B', yblocks)
   print ('C', blocks)
   seqList' (seqList' seqPixel) pixels `seq` return ()


main :: IO ()
main = do
  filedes <- openFile "scene.spd" ReadMode
  filestring <- hGetContents filedes
  (scene,s) <- return $ head $ reads filestring
  print $ "leftover:" ++ s
  display scene
  display scene
  display scene

display :: Scene -> IO ()
display scene = do
  t1 <- getPOSIXTime
  gen_blocks_list 512 512 128 scene
  t2 <-  getPOSIXTime
  print (t2-t1)

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to