#2545: Data Parallel Haskell on Kubuntu 8.04 uses too much memory
----------------------------+-----------------------------------------------
    Reporter:  jjanssen     |       Owner:          
        Type:  bug          |      Status:  new     
    Priority:  normal       |   Component:  Compiler
     Version:  6.8.3        |    Severity:  normal  
    Keywords:  Memory Leak  |    Testcase:          
Architecture:  x86          |          Os:  Linux   
----------------------------+-----------------------------------------------
 Hey.

 I tried to perform some tests on the performance of data parallel haskell
 today using the program from the DPH-wiki:

 {{{
 {-# OPTIONS -fparr -fglasgow-exts #-}
 module Main
 where
 import GHC.PArr

 dotp :: Num a => [:a:] -> [:a:] -> a
 dotp xs ys = sumP [:x*y | x <- xs | y <- ys:]

 main = putStrLn $ show $ dotp [:1..500000:] [:5..4999995:]
 }}}

 After compiling this with -threaded and running it, the memory usage
 starts to increase up until the point that the machine starts swapping.
 On a machine with 2GiB of memory, this hardly seems to be normal
 behaviour, especially since a program like this should presumably take up
 maximally 3*the size of the vectors used, which would translate to
 3*500.000*32 bit = 6MiB.  So this seems like a bug.

 I tried it with the GHC 6.8.2 that is in the kubuntu repositories and with
 the GHC 6.8.3 binaries distributed on the GHC website.  Both showed the
 same behaviour.  Also, the behaviour does not seem to depend on the usage
 of +RTS -N2, as both with and without these flags the memory gets filled.

 Additionally, I remember having similar problems when trying out parMap_
 on an example, but I can't seem to find the example right now.

 Hopefully this gets fixed (or maybe already is), so I can start using the
 power of DPH to optimise some of my programs.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/2545>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to