RE: Two problems with heap profiling

On 16 April 2004 10:39, Stefan Reich wrote:
I'm using GHC 6.2.1 on Windows 2000.
Problem 1: -hr crashes in some circumstances.
Take this program (Test.hs):
module Main where import IO main = do readFile "large.csv" putStrLn "OK"
where large.csv is an 800K CSV file (with very small files, the bug doesn't occur). I compile with:
ghc -prof -auto-all Test.hs
and run with:
a.out +RTS -hr
I can't reproduce this bug. Just to make sure I'm doing exactly the same thing, could you send me the source code for Test.hs and "large.csv" (compressed), please? Cheers, Simon

Hi Simon, I found a suitable large file that is certainly on your harddisk - the GHC 6.2.1 user's guide (users_guide.ps, 1205288 bytes) :-) I attached new Haskell source file (you will need to adapt the file path). Compilation and invocation as in my previous mail. The program crashes every time I run it (Windows XP this time, but I assume that doesn't make a difference). Thanks in advance for your help, -Stefan Simon Marlow wrote:
On 16 April 2004 10:39, Stefan Reich wrote:
I'm using GHC 6.2.1 on Windows 2000.
Problem 1: -hr crashes in some circumstances.
Take this program (Test.hs):
module Main where import IO main = do readFile "large.csv" putStrLn "OK"
where large.csv is an 800K CSV file (with very small files, the bug doesn't occur). I compile with:
ghc -prof -auto-all Test.hs
and run with:
a.out +RTS -hr
I can't reproduce this bug. Just to make sure I'm doing exactly the same thing, could you send me the source code for Test.hs and "large.csv" (compressed), please?
Cheers, Simon
module Main where import IO main = do contents <- readFile "/ghc/ghc-6.2.1/doc/users_guide.ps" putStrLn $ "lines: " ++ show (length (lines contents))

Stefan Reich wrote:
[...] The program crashes every time I run it (Windows XP this time, but I assume that doesn't make a difference).
Hmmm, it works with GHC 6.2.1 and the one from the HEAD on my x86 Linux box. Perhaps something WinDoze-related, I don't know => SimonM... Cheers, S.

Yes, same thing here on RedHat 9... apparently a problem specific to the Windows port. -Stefan Sven Panne wrote:
Stefan Reich wrote:
[...] The program crashes every time I run it (Windows XP this time, but I assume that doesn't make a difference).
Hmmm, it works with GHC 6.2.1 and the one from the HEAD on my x86 Linux box. Perhaps something WinDoze-related, I don't know => SimonM...
Cheers, S.
participants (3)
-
Simon Marlow
-
Stefan Reich
-
Sven Panne