#3133: Biographical profiling segfaults
-----------------------+----------------------------------------------------
Reporter: basvandijk | Owner:
Type: bug | Status: new
Priority: normal | Component: Profiling
Version: 6.10.1 | Severity: blocker
Keywords: | Testcase:
Os: Linux | Architecture: Unknown/Multiple
-----------------------+----------------------------------------------------
When I try to make a biographical profile of my program I get a
segmentation fault:
{{{
$ ghc --make <prog>.hs -prof -auto-all
$ ./<prog> +RTS -hb
Segmentation fault
}}}
Note that I don't get a segmentation fault when I run the program without
-hb or generate other memory usage profiles.
Also note that the program itself probably doesn't matter: I tried two
different programs and got a segmentation fault each time. For what it's
worth, here are they:
{{{
module Main where
import System.Environment (getArgs)
main :: IO ()
main = print . sum . enumFromTo (0::Int) . read . head =<< getArgs
}}}
{{{
module Main where
import Prelude hiding (foldl)
import System.Environment (getArgs)
foldl :: (b -> a -> b) -> b -> [a] -> b
foldl f z [] = z
foldl f z (x:xs) = let z' = f z x
in foldl f z' xs
sum2 :: [Int] -> Int
sum2 = foldl (+) 0
main :: IO()
main = print
. sum2
. enumFromTo 1
. read
. head =<< getArgs
}}}
Info:
{{{
$ ghc --version
The Glorious Glasgow Haskell Compilation System, version 6.10.1
$ uname -a
Linux bassbox 2.6.27-gentoo-r8 #4 PREEMPT Mon Mar 23 10:33:24 CET 2009
i686 AMD Athlon(tm) 64 Processor 3200+ AuthenticAMD GNU/Linux
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3133>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs