[GHC] #8834: 64-bit windows cabal.exe segfaults in GC
GHC
ghc-devs at haskell.org
Mon Mar 10 08:36:17 UTC 2014
#8834: 64-bit windows cabal.exe segfaults in GC
----------------------------------+----------------------------------
Reporter: awson | Owner:
Type: bug | Status: patch
Priority: highest | Milestone: 7.8.1
Component: Compiler | Version: 7.8.1-rc2
Resolution: | Keywords:
Operating System: Windows | Architecture: x86_64 (amd64)
Type of failure: Runtime crash | Difficulty: Unknown
Test Case: | Blocked By:
Blocking: | Related Tickets:
----------------------------------+----------------------------------
Comment (by jstolarek):
awson, great bisecting job here!
The intention behind the faulty commit is that both older and newer
implementations are semantically identical (which turns out not to be the
case) but the newer one avoids code duplication.
> I think your analysis is right, that it is the change to okToInline that
is at fault.
Two other possibilities include:
1. `conflict` function
2. instance definition for `GlobalReg` datatype in
[[GhcFile(compiler/cmm/CmmNode.hs)]] in the `DefinerOfRegs`. That's the
place were we say what global registers are defined (and therefore
clobbered) by each Cmm node.
awson, to pin this bug we have to know the difference between correct and
incorrect Cmm. Could you compile your minimal example with GHC HEAD (which
will give us the segfaulting Cmm) and with your patched version (which
will give us working Cmm) and upload them here? Dump the Cmm with `-ddump-
cmm` flag. I see that you're calling `print` in your example. My
experience is that it adds a lot of extra Cmm to analyse. Could you see if
splitting your code into two modules also causes the bug:
{{{
module T8834 where
import qualified Data.ByteString.Char8 as BSS
T8834 :: IO Int
T8834 = do
cache <- BSS.readFile "00-index.cache"
return (length $ BSS.lines cache)
}}}
{{{
module Main where
import T8834
main :: IO ()
main = T8834 >>= print
}}}
If this also causes the bug then most likely we only need Cmm dump for
`T8834` module.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8834#comment:10>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list