[GHC] #8974: 64 bit windows executable built with ghc-7.9.20140405+LLVM segfaults
GHC
ghc-devs at haskell.org
Sat Oct 15 02:21:42 UTC 2016
#8974: 64 bit windows executable built with ghc-7.9.20140405+LLVM segfaults
------------------------------------+--------------------------------------
Reporter: awson | Owner:
Type: bug | Status: new
Priority: high | Milestone: 8.0.1
Component: Compiler (LLVM) | Version: 7.9
Resolution: | Keywords:
Operating System: Windows | Architecture: x86_64 (amd64)
Type of failure: Runtime crash | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
------------------------------------+--------------------------------------
Comment (by GordonBGood):
Replying to [comment:46 Phyx-]:
> Binutils 2.27-2 has been released on msys, this contains Awson's patch.
> I need to boil down a version that consistently fails using -fllvm (with
the patch on 64-bit Windows) and not without and will submit it here...
Failure code as follows:
{{{
{-# LANGUAGE FlexibleContexts #-}
{-# OPTIONS_GHC -O3 -rtsopts #-} -- or O2
import Data.Array.ST (runSTUArray)
import Data.Array.Base
numLOOPS = 50000 :: Integer
-- Uses a very simple Sieve of Eratosthenes to 2 ^ 18 (so one L1 cache
size).
test :: () -> [Int]
test() = 2 : [fromIntegral i * 2 + 3 | (i, False) <- assocs bufb] where
bufb = runSTUArray $ do
let bfLmt = (256 * 1024) `div` 2 - 1 -- to 2^18 + 2 is 128 KBits - 1 =
16 KBytes
cmpstsb <- newArray (0, bfLmt) False :: ST s (STUArray s Int Bool)
let loop n = -- cull a number of times to test timing
if n <= 0 then return cmpstsb else loop (n - 1)
loop numLOOPS
main = print $ length $ test()
}}}
The above code consistently segfaults with 64-bit GHC 8.0.1 with LLVM 3.7
with the latest MSYS2_64 including the patch on Windows when compiled with
the -fllvm flag but not on Linux 64-bit (Fedora 24) under the same
conditions or without the -fllvm flag (defaulting to using NCG).
It does not segfault if 'numLOOPS' is made only 1000 or if the type of
'numLOOPS' is changed from multi-precision 'Integer' to base 'Int' (64-bit
integer value for 64-bit systems). I suspect there is a value such as
32768 where the segfault starts when using 'Integer'.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8974#comment:48>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list