[GHC] #8573: "evacuate: strange closure type 0" when creating large array
GHC
ghc-devs at haskell.org
Fri Nov 29 14:43:37 UTC 2013
#8573: "evacuate: strange closure type 0" when creating large array
----------------------------+----------------------------------
Reporter: nad | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.6.3
Keywords: | Operating System: Linux
Architecture: x86 | Type of failure: Runtime crash
Difficulty: Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: |
----------------------------+----------------------------------
Consider the following code:
{{{
module Main where
import Data.Array
xs :: [Int]
xs = [0 .. 64988]
crash :: Int -> IO ()
crash m = array (0, m) [ (x, x) | x <- xs ] `seq` return ()
strangeClosureType = do
print (sum xs)
crash (maxBound - 1)
segFault1 = crash (maxBound - 1)
segFault2 = do
print (sum xs)
crash (maxBound - 2)
}}}
If I compile the program using `ghc --make Main.hs -O -main-is
strangeClosureType`, then I get the following error message:
{{{
Main: internal error: evacuate: strange closure type 0
(GHC version 7.6.3 for i386_unknown_linux)
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
Aborted (core dumped)
}}}
If I don't use `-O`, or if I let `segFault1` or `segFault2` be `main`,
then I get the following error message instead:
{{{
Segmentation fault (core dumped)
}}}
If the number `30000` is replaced by some other number, then the strange
closure error may be replaced by a segfault, or even no error at all.
Perhaps this is another instance of bug #7762; I have only tested using
GHC 7.6.3.
I am using base 4.6.0.1 and array 0.4.0.1.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8573>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list