[GHC] #8974: 64 bit windows executable built with ghc-7.9.20140405+LLVM segfaults
GHC
ghc-devs at haskell.org
Mon Oct 17 06:32:10 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:49 awson]:
> Can't reproduce this neither with ghc-8.0.1.20160826+llvm-3.7, nor with
ghc-8.1.20160921+llvm-4.0(HEAD). I have no segfaults in both cases (tried
to increase numLOOPS to 100000 and 200000 -- no segfaults either).
>
> Perhaps, that was a bug in GHC which was fixed since 8.0.1 release?
@awson, Perhaps it has been fixed which would be good - I'm using 64-bit
Haskell Platform with stock/stable 8.0.1.
I'm also having segfaults with -fllvm and not without even though I don't
believe it's using 'Integer' with the following paged Sieve of
Eratosthenes code:
{{{
{-# LANGUAGE FlexibleContexts #-}
{-# OPTIONS_GHC -O3 -rtsopts #-} -- or O2
import Data.Bits
import Data.Array.Base
import Data.Array.ST (runSTUArray, STUArray(..))
type PrimeType = Int
range = 1000000 :: PrimeType
szPGBTS = (2^14) * 8 :: PrimeType -- CPU L1 cache in bits
szBPBTS = (2^7) * 8 :: PrimeType -- base primes pages can be much smaller
primesPages :: PrimeType -> [UArray PrimeType Bool]
primesPages szpgbts = pagesFrom 0 szPGBTS bppgs where
makePg lowi szbts bps = runSTUArray $ do
let limi = lowi + szbts - 1
let nxt = 3 + limi + limi -- last candidate in range
cmpsts <- newArray (lowi, limi) False
let pbts = fromIntegral szbts
let cull (p:ps) =
let sqr = p * p in
if sqr > nxt then return cmpsts
else let pi = fromIntegral p in
let cullp c = if c > pbts then return ()
else do
unsafeWrite cmpsts c True
cullp (c + pi) in
let a = (sqr - 3) `shiftR` 1 in
let s = if a >= lowi then fromIntegral (a - lowi)
else let r = fromIntegral ((lowi - a) `rem` p) in
if r == 0 then 0 else pi - r in
do { cullp s; cull ps }
if bps == [] then do
pg0 <- unsafeFreezeSTUArray cmpsts
cull $ listPagePrms [pg0]
else cull bps
pagesFrom lowi bts bps =
let cf lwi = case makePg lwi bts bps of
pg -> pg `seq` pg : cf (lwi + bts) in cf lowi
bppgs = -- secondary stream of primes
listPagePrms (makePg 0 szBPBTS [] : (pagesFrom szBPBTS szBPBTS bppgs))
listPagePrms :: [UArray PrimeType Bool] -> [PrimeType]
listPagePrms (hdpg @ (UArray lowi _ rng _) : tlpgs) =
let loop i = if i >= rng then listPagePrms tlpgs
else if unsafeAt hdpg i then loop (i + 1)
else let ii = lowi + fromIntegral i in
case 3 + ii + ii of
p -> p `seq` p : loop (i + 1) in loop 0
primesPaged :: () -> [PrimeType]
primesPaged() = 2 : (listPagePrms $ primesPages szPGBTS)
main = print $ length $ takeWhile ((>=) range) $ primesPaged()
}}}
The above segfaults for the "range" set to a million, but not for some
lesser values (ie. a hundred thousand) for '-fllvm' with the same
environment as before.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8974#comment:50>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list