[GHC] #8834: 64-bit windows cabal.exe segfaults in GC

#8834: 64-bit windows cabal.exe segfaults in GC ----------------------------------+--------------------------------- Reporter: awson | Owner: Type: bug | Status: new Priority: highest | Milestone: 7.8.1 Component: None | Version: 7.8.1-rc2 Keywords: | Operating System: Windows Architecture: x86_64 (amd64) | Type of failure: None/Unknown Difficulty: Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | ----------------------------------+--------------------------------- `cabal.exe` built with 64-bit windows GHC segfaults doing `cabal configure` or `cabal install` or probably something else. This occurs *both* for cabal-install 1.18.0.2 built against Cabal 1.18.1.2 and for cabal-install 1.18.0.3 built against Cabal 1.18.1.3. This occurs only for 64-bit build, 32-bit build is fine. 64-bit GHC-7.6.3 build is also fine. During debugging I see segfault occurs inside `evacuate` somewhere near `get_itbl` call I guess. If I make `cabal.exe` to not trigger some presumably bad GC compiling it with `-rtsopts` and running it as (for example) {{{cabal +RTS -H256m -m50 -RTS ...}}} the problem disappears. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8834: 64-bit windows cabal.exe segfaults in GC ---------------------------------+---------------------------------- Reporter: awson | Owner: Type: bug | Status: new Priority: highest | Milestone: 7.8.1 Component: None | Version: 7.8.1-rc2 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: ---------------------------------+---------------------------------- Comment (by awson): Probably, it's worth to add that I observed this problem since I was able to build 64-bit windows GHC 7.7+ (a month or so). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8834: 64-bit windows cabal.exe segfaults in GC ---------------------------------+---------------------------------- Reporter: awson | Owner: Type: bug | Status: new Priority: highest | Milestone: 7.8.1 Component: None | Version: 7.8.1-rc2 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: ---------------------------------+---------------------------------- Comment (by awson): 1. I've reduced this case to the following: {{{ import qualified Data.ByteString.Char8 as BSS main :: IO () main = do cache <- BSS.readFile "00-index.cache" print (length $ BSS.lines cache) }}} `00-index.cache` is hackage packages cache file. Even truncated to 12000 lines it gives segfault. 2. After bisecting I've found the [https://github.com/ghc/ghc/commit/ad15c2b4bd37082ce989268b3d2f86a2cd34386a problematic commit]. I don't understand what is going here. I think I've made absolutely my best in this situation. Please, someone fix this! I feel myself completely alone fighting with numerous win64 bugs which nobody ever bother to look into. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8834: 64-bit windows cabal.exe segfaults in GC ---------------------------------+---------------------------------- Reporter: awson | Owner: Type: bug | Status: new Priority: highest | Milestone: 7.8.1 Component: None | Version: 7.8.1-rc2 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: ---------------------------------+---------------------------------- Comment (by awson): Since things were changed since that commit, I've revised it and made manual reversal. This commit was mainly a set of comments, relevant changes were more or less local and I've created this reversal patch mechanically. I still don't understand underlying machinery, but it looks this patch makes things work again on win64. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8834: 64-bit windows cabal.exe segfaults in GC ---------------------------------+---------------------------------- Reporter: awson | Owner: Type: bug | Status: patch Priority: highest | Milestone: 7.8.1 Component: None | Version: 7.8.1-rc2 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: ---------------------------------+---------------------------------- Changes (by awson): * status: new => patch Comment: I've tested this reversal patch and all works fine. Moreover, it is not platform-specific, so it probably fix other weird segfaults on other platforms. That [https://github.com/ghc/ghc/commit/ad15c2b4bd37082ce989268b3d2f86a2cd34386a problematic commit] is particularly suspicious because if gets rid of `callerSaves` - the only explicitly platform-specific function used in `CmmSink.hs`. That looks very strange. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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: ----------------------------------+---------------------------------- Changes (by awson): * failure: None/Unknown => Runtime crash * component: None => Compiler -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 refold): Would be nice if @jstolarek (the author of that commit) could comment. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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: ----------------------------------+---------------------------------- Changes (by simonpj): * cc: simonmar, jstolarek (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 simonmar): @awson thanks for all the diagnosis, sorry you have to be the one to do all this. I don't think there are any other regular developers building and testing on 64-bit Windows. I hope that when we get nightly builds working again things will improve. I think your analysis is right, that it is the change to `okToInline` that is at fault. Would you mind doing one more test for me? I'd like to know whether it still works if you don't revert the changes to `isTrivial`, which I believe should be fine. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 simonpj): Could this account for #8870? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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

#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 awson): Well, separating to modules also causes the bug. I put Cmm dumps here. But is this enough? Could the bug manifest itself somewhere else (e. g. `base` or `bytestring` libraries)? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 awson): @simonmar, unreverting `isTrivial` brokes things again. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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): I see something that looks suspicious. In the correct version we have: {{{ c1zB: _r1xg::P64 = R1; if ((Sp + -16) < SpLim) goto c1zC; else goto c1zD; c1zC: R1 = _r1xg::P64; call (stg_gc_enter_1)(R1) args: 8, res: 0, upd: 8; c1zD: (_c1zx::I64) = call "ccall" arg hints: [PtrHint, PtrHint] result hints: [PtrHint] newCAF(BaseReg, _r1xg::P64); if (_c1zx::I64 == 0) goto c1zz; else goto c1zy; c1zz: call (I64[_r1xg::P64])() args: 8, res: 0, upd: 8; c1zy: I64[Sp - 16] = stg_bh_upd_frame_info; I64[Sp - 8] = _c1zx::I64; R2 = c1zA_str; Sp = Sp - 16; call GHC.CString.unpackCString#_info(R2) args: 24, res: 0, upd: 24; }}} In the incorrect one we have: {{{ c1zy: if ((Sp + -16) < SpLim) goto c1zz; else goto c1zA; c1zz: R1 = R1; call (stg_gc_enter_1)(R1) args: 8, res: 0, upd: 8; c1zA: (_c1zu::I64) = call "ccall" arg hints: [PtrHint, PtrHint] result hints: [PtrHint] newCAF(BaseReg, R1); if (_c1zu::I64 == 0) goto c1zw; else goto c1zv; c1zw: call (I64[R1])() args: 8, res: 0, upd: 8; c1zv: I64[Sp - 16] = stg_bh_upd_frame_info; I64[Sp - 8] = _c1zu::I64; R2 = c1zx_str; Sp = Sp - 16; call GHC.CString.unpackCString#_info(R2) args: 24, res: 0, upd: 24; }}} Notice how correct version saves `R1` to local variable. I'm especially worried about this call: {{{ call (I64[_r1xg::P64])() args: 8, res: 0, upd: 8; CORRECT.CMM call (I64[R1])() args: 8, res: 0, upd: 8; WRONG.CMM }}} '''If''' `R1` gets clobbered be earlier ccall to `newCAF(BaseReg, R1)` then this is probably the reason why things go wrong. In that case the right solution would be to tell GHC that the call to `newCAF` defines register `R1` (see `DefinerOfRegs` instance declaration for `GlobalReg`). Then this case should be caught by first guard in `conflicts`. Also, Note [Sinking and calls] seems very relevant here. As a side note: it is really annoying to see these `R1 = R1` assignments. I recall they are eliminated by the code generator but it is frustrating to see them at the Cmm level. I believe the sinking pass should eliminate these assignments but I didn't have enough time to investigate into this further during my internship. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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): Replying to [comment:12 awson]:
@simonmar, unreverting `isTrivial` brokes things again.
So this works: {{{ isTrivial :: CmmExpr -> Bool isTrivial (CmmReg _) = True isTrivial _ = False }}} but this doesn't: {{{ isTrivial :: CmmExpr -> Bool isTrivial (CmmReg (CmmLocal _)) = True isTrivial _ = False }}} ? I know this is slightly different from your patch (it ignores literals which I believe are irrelevant here). Again, would be nice to see differences in Cmm between the two. simonmar: could you tell us whether the call to `newCAF` clobbers `R1` ? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 awson): Replying to [comment:14 jstolarek]:
So this works:
{{{ isTrivial :: CmmExpr -> Bool isTrivial (CmmReg _) = True isTrivial _ = False }}}
but this doesn't:
{{{ isTrivial :: CmmExpr -> Bool isTrivial (CmmReg (CmmLocal _)) = True isTrivial _ = False }}}
Conversely. The first does not work, the second works. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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):
Conversely. The first does not work, the second works.
Yes, you're right. It should be other way around. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 simonmar): I think the bad code is much more likely to be in a library somewhere, not in the code that calls `readFile`/`lines`, so we're not going to see anything bad in that file. @jstolarek - R1 is not caller-saves (on either Linux or Win64), so it is safe to leave it live across a foreign call. Also, that code fragment is the standard `newCAF` call which appears everywhere, if this was broken then everything would be broken. I'm surprised that the change to `isTrivial` all by itself causes this failure. That must mean that there was something wrong with the code before the "bad patch", because the change to `isTrivial` should be safe. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 simonmar): It's looking more likely that there is a bug related to caller-saves registers somewhere else, and the change to `isTrivial` tickles it by making `CmmSink` more eager to inline `GlobalReg`s. This is affecting Win64 because that platform has a different C calling convention, with different caller-saves registers. So either we have a bad optimisation (probably in `CmmSink`), or the specification for what is a caller-saves reg on Win64 is wrong (`includes/stg/MachRegs.h`). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 awson): Replying to [comment:17 simonmar]:
I'm surprised that the change to `isTrivial` all by itself causes this failure. That must mean that there was something wrong with the code before the "bad patch", because the change to `isTrivial` should be safe.
It probably would worth to add that reverting `isTrivial` only does not help either. I. e. `isTrivial` all by itself broke things as they were before that bad commit, but changing *only* `isTrivial` to it's pre-commit state does not help either. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:19 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 simonpj): Could this have anything to do with #8870, a much simpler case than Cabal? (As #8870 says, I can't even build a working stage-2 GHC on Windows now.) Both this and #8870 look like release blockers to me. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:20 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 awson): Replying to [comment:20 simonpj]:
Could this have anything to do with #8870, a much simpler case than Cabal?
(As #8870 says, I can't even build a working stage-2 GHC on Windows now.)
Both this and #8870 look like release blockers to me.
Simon
I can't reproduce #8870 using 32-bit GHC on 64-bin Windows. Are you using 32-bit Windows? If no, then your problem can be different from #8870 (but still related to #8834). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:21 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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): Bug report says:
During debugging I see segfault occurs inside `evacuate` somewhere near `get_itbl` call I guess.
Can someone tell me what is `evacuate` and `get_itbl`? Are these functions in the RTS? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:22 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 awson): Yes, they are in RTS. More precise location is rts/sm/Evac.c line 390. Also I think this bug is triggered near foreign `memchr` call in function `elemIndex` from `Data.ByteString` module in `bytestring` package, which is inlined down to `lines` function from `Data.ByteString.Char8`. Also I checked this bug is not triggered if relevant modules from `bytestring` package are compiled with `-O` flag instead of `-O2`, hence this bug could be more ubiquitous if more applications code was compiled with `-O2`, perhaps. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:23 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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):
Also I checked this bug is not triggered if relevant modules from `bytestring` package are compiled with `-O` flag instead of `-O2`
That's interesting. Looking at `DynFlags.lhs` I see two optimisations that are enabled only with `-O2`: liberate case and SpecConstr. I admit have no idea what they do. Suggestions please?
Also I think this bug is triggered near foreign `memchr` call in function `elemIndex` from `Data.ByteString` module in bytestring package, which is inlined down to lines function from `Data.ByteString.Char8`.
It would be great if we had a test case that does not depend on any library code. This way we could eyeball the problem by looking at Cmm. Do you think you would be able to create such a test case. I got my hands on 64-bit Windows, I'm building GHC at the moment so I'll try to look into this one. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:24 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 thoughtpolice): It's not true that those are the *only* things enabled by -O2 - you must also search for `optLevel`, which client code can depend on for specific instances if they wish (for example, maybe it's *not* an entire Core->Core pass, but an otherwise small micro-optimization). Actually, now that I'm searching and thinking about it - the only other case where we do this is when we short-cut PAPs - see 4d1ea482885481073d2fee0ea0355848b9d853a1 and `Note [avoid intermediate PAPs]` in `StgCmmLayout`. Simon committed this a while ago. I also have a Win32 build going, so I'll test this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:25 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 thoughtpolice): (To be clear: by 'test this' I mean reverting that). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:26 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

It would be great if we had a test case that does not depend on any
#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 awson): Replying to [comment:24 jstolarek]: library code. This way we could eyeball the problem by looking at Cmm. Do you think you would be able to create such a test case. I think, this code should be enough: {{{ module BugIso (lines1) where import Prelude hiding (null, take, drop) import Data.ByteString hiding (elemIndex) import Data.ByteString.Internal import Data.Word import Foreign elemIndex1 :: Word8 -> ByteString -> Maybe Int elemIndex1 c (PS x s l) = inlinePerformIO $ withForeignPtr x $ \p -> do let p' = p `plusPtr` s q <- memchr p' c (fromIntegral l) return $! if q == nullPtr then Nothing else Just $! q `minusPtr` p' {-# INLINE elemIndex1 #-} elemIndex :: Char -> ByteString -> Maybe Int elemIndex = elemIndex1 . c2w {-# INLINE elemIndex #-} lines1 :: ByteString -> [ByteString] lines1 ps | null ps = [] | otherwise = case search ps of Nothing -> [ps] Just n -> take n ps : lines1 (drop (n+1) ps) where search = elemIndex '\n' }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:27 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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):
It's not true that those are the *only* things enabled by -O2
Just to be clear, I only said they are the only `-O2` things enabled in `DynFlags`.
I think, this code should be enough:
Yes, I can confirm that it segfaults. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:28 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 thoughtpolice): I can confirm Kyril's example above works properly and produces the segfault as well. Here's my updated version: {{{#!haskell module Main (main) where import Prelude hiding (null, take, drop) import Data.ByteString hiding (elemIndex) import qualified Data.ByteString as B import Data.ByteString.Internal import Data.Word import Foreign elemIndex1 :: Word8 -> ByteString -> Maybe Int elemIndex1 c (PS x s l) = inlinePerformIO $ withForeignPtr x $ \p -> do let p' = p `plusPtr` s q <- memchr p' c (fromIntegral l) return $! if q == nullPtr then Nothing else Just $! q `minusPtr` p' {-# INLINE elemIndex1 #-} elemIndex :: Char -> ByteString -> Maybe Int elemIndex = elemIndex1 . c2w {-# INLINE elemIndex #-} lines1 :: ByteString -> [ByteString] lines1 ps | null ps = [] | otherwise = case search ps of Nothing -> [ps] Just n -> take n ps : lines1 (drop (n+1) ps) where search = elemIndex '\n' main = do f <- B.readFile "00-index.cache" print (Prelude.length $ lines1 f) }}} You can grab the `00-index.cache` file from `/c/Users/$USER/AppData/Roaming/cabal/packages/hackage.haskell.org/00-index.cache` I'm investigating reverting the PAP patch (still building). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:29 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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): I applied awson's patch that reverts some of my changes in `CmmSink` and surprisingly I'm still getting a segfault with code posted in comment [[comment:#27]]. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:30 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 awson): Replying to [comment:30 jstolarek]:
I applied awson's patch that reverts some of my changes in `CmmSink` and surprisingly I'm still getting a segfault with code posted in comment [[comment:#27]].
Very strange. I have no segfault here with patched HEAD. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:31 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 simonmar): Could someone post Cmm for the working and non-working versions please? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:32 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 awson): These are versions, compiled with `-O2 -fmax-simplifier-iterations=10 -fdicts-cheap -fspec-constr-count=6` (`bytestring` package flags) by 7.8rc2 (bad) and patched HEAD (good). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:33 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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): Could you also post cmm dumps for `-O1` and unpatched GHC? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:34 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 simonmar): Here is the broken bit of code, from `lines1_bad`: {{{ c2gC: _s2cV::I64 = R5; _s2cY::I64 = R2 + R4; _c2f5::I64 = R5; (_s2d3::I64) = call "ccall" arg hints: [PtrHint, `signed',] result hints: [PtrHint] memchr(_s2cY::I64, 10, _c2f5::I64); if (_s2d3::I64 == 0) goto c2gK; else goto c2gL; c2gK: call MO_Touch(R3); I64[Hp - 128] = Data.ByteString.Internal.PS_con_info; P64[Hp - 120] = R3; I64[Hp - 112] = R2; I64[Hp - 104] = R4; I64[Hp - 96] = _s2cV::I64; I64[Hp - 88] = :_con_info; P64[Hp - 80] = Hp - 127; P64[Hp - 72] = GHC.Types.[]_closure+1; _c2gw::P64 = Hp - 86; Hp = Hp - 72; R1 = _c2gw::P64; call (P64[Sp])(R1) args: 8, res: 0, upd: 8; }}} Note how R2, R3 and R4 are live across the C call. This is wrong, because on Win64, R3 and R4 are caller-saves and therefore clobbered by the C call. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:35 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

Note how R2, R3 and R4 are live across the C call. This is wrong, because on Win64, R3 and R4 are caller-saves and therefore clobbered by
#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): the C call. Just to clarify: floating of R2 is correct? `MachRegs.h` defines R3 and R4 correctly as caller saves: {{{ #if !defined(mingw32_HOST_OS) #define CALLER_SAVES_R3 #define CALLER_SAVES_R4 #endif }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:36 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 awson): All looks quite the contrary: {{{ ... #define REG_R2 r14 #define REG_R3 rsi #define REG_R4 rdi ... }}} [http://msdn.microsoft.com/en-us/library/6t169e9c.aspx The registers RBX, RBP, RDI, RSI, RSP, R12, R13, R14, and R15 are considered nonvolatile...] And we have *not defined* here: {{{ #if !defined(mingw32_HOST_OS) #define CALLER_SAVES_R3 #define CALLER_SAVES_R4 }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:37 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 simonmar): Ah, you're right, my apologies, I misread the conditional in `MachRegs.h`. So the problem is elsewhere... time for gdb? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:38 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 simonpj): So where are we on this? * Simon M says "here is the broken bit of code" (comment 35), and then says "I misread" (comment 38). Does that mean that the broken bit of code isn't broken? * If we use Karel's reversion patch (between comments 2 and 3 above) does that cure all known crashes? I confirm that it ''does'' fix my own "ghc- stage2 segfaults" problem, reported in #8870. But what about the hello- world problem in #8834, and Ganesh's new report in #8890? * If reverting the `CmmSink` change does in fact solve the problem, we should probably go ahead and revert it, and un-block the GHC 7.8 release. * But even if we do that we are still stuck with not knowing WHY it solves the problem. Perhaps the patch was fine, but it exposes a problem somewhere else? And we really want the `CmmSink` improvements. We really need someone to dig into it with GDB. Austin, can you get a Windows box on the network that exhibits the bug, so that Simon M can crank up gdb? Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:39 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 awson): Replying to [comment:39 simonpj]:
* If we use Karel's reversion patch
I'm Kyrill, not Karel. Extremely sorry for OT. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:40 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 awson): I've inspected "bad" Cmm a bit and found [https://ghc.haskell.org/trac/ghc/attachment/ticket/8834/lines1_bad#L2276 this]: {{{ call (stg_gc_fun)(R1) args: 40, res: 0, upd: 8; c2gF: if (%MO_S_Le_W64(R5, 0)) goto c2gB; else goto c2gC; }}} `R5` is `r8` and is volatile on Win64. I don't see it restored before `%MO_S_Le_W64(R5, 0)` (honestly, I don't know what `%MO_S_Le_W64(R5, 0)` is). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:41 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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):
I don't know what %MO_S_Le_W64(R5, 0) is
MO = Machine Operation S = Signed Le = less-equal W64 = 64-bit word It's a !PrimOp (ie. a built-in machine operation) that checks whether R5 is less or equal to 0.
Could it be that another patch interacts badly with stg_gc_fun?
I believe this patch should be irrelevant. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:42 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 awson): But, AFAIUI, `R5` shall be restored anyway after calling `stg_gc_fun`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:43 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 simonmar):
Simon M says "here is the broken bit of code" (comment 35), and then says "I misread" (comment 38). Does that mean that the broken bit of code isn't broken?
If we use Karel's reversion patch (between comments 2 and 3 above) does
Correct, we still don't know what's broken. that cure all known crashes? I confirm that it does fix my own "ghc-stage2 segfaults" problem, reported in #8870. But what about the hello-world problem in #8834, and Ganesh's new report in #8890?
If reverting the CmmSink change does in fact solve the problem, we should probably go ahead and revert it, and un-block the GHC 7.8 release.
But even if we do that we are still stuck with not knowing WHY it solves the problem. Perhaps the patch was fine, but it exposes a problem somewhere else? And we really want the CmmSink improvements. We really need someone to dig into it with GDB. Austin, can you get a Windows box on the network that exhibits the bug, so that Simon M can crank up gdb?
I doubt that the patch actually introduced the bug, since @awson said that just the single change to `isTrivial` is enough to trigger the crash. Still, this patch isn't really essential - it made it possible to run `CmmSink` before stack layout, but measurements showed that it didn't buy anything to do that, so we're not currently using that functionality. The other thing in the patch is the `isTrivial` change that makes it more keen to inline `GlobalReg`s and literals; this is a very small win (<1%, IIRC). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:44 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 awson): [https://ghc.haskell.org/trac/ghc/attachment/ticket/8834/lines1_good#L2295 Corresponding code] from "good" cmm is: {{{ I64[Sp - 32] = _s2d4::I64; P64[Sp - 24] = _s2d5::P64; I64[Sp - 16] = _s2d6::I64; I64[Sp - 8] = _s2d7::I64; Sp = Sp - 32; call (stg_gc_fun)(R1) args: 40, res: 0, upd: 8; c2gR: if (%MO_S_Le_W64(_s2d7::I64, 0)) goto c2gN; else goto c2gO; }}} Not that it restores `R5` - it use no `R5` at all. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:45 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 simonmar): @awson - the call to `stg_gc_fun` doesn't return (there's no "returns to" annotation on it). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:46 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 awson): Ah, thanks, assembler intuition was wrong for Cmm :) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:47 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8834: 64-bit windows cabal.exe segfaults in GC ----------------------------------+---------------------------------- Reporter: awson | Owner: jstolarek 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: ----------------------------------+---------------------------------- Changes (by jstolarek): * owner: => jstolarek Comment: Looking into this at the moment. I have a few interesting findings, will post later. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:48 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8834: 64-bit windows cabal.exe segfaults in GC
----------------------------------+----------------------------------
Reporter: awson | Owner: jstolarek
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 Simon Peyton Jones

#8834: 64-bit windows cabal.exe segfaults in GC ----------------------------------+---------------------------------- Reporter: awson | Owner: jstolarek 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): Simon, could we get a day or two more for this one? I'm at the very moment writing a summary of what I've learned so far and I believe it will get us very close to fixing this bug properly. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:50 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8834: 64-bit windows cabal.exe segfaults in GC ----------------------------------+---------------------------------- Reporter: awson | Owner: jstolarek 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 simonpj): I don't think Austin is planning to make the final release in the next day or two, so yes, please go ahead. My reversion was just to un-glue the Windows builds which otherwise are totally stuck. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:51 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8834: 64-bit windows cabal.exe segfaults in GC ----------------------------------+---------------------------------- Reporter: awson | Owner: jstolarek 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): Replying to [comment:50 jstolarek]:
Simon, could we get a day or two more for this one? I'm at the very moment writing a summary of what I've learned so far and I believe it will get us very close to fixing this bug properly.
According to my experiments you can fix Windows build easily by changing definition of `isTrivial` in !CmmSink to: {{{ isTrivial :: CmmExpr -> Bool isTrivial (CmmReg (CmmLocal _)) = True isTrivial (CmmLit _) = True isTrivial _ = False }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:52 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8834: 64-bit windows cabal.exe segfaults in GC ----------------------------------+---------------------------------- Reporter: awson | Owner: jstolarek 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 simonpj): Fine. But reversion works fine too, right? I'm not suggesting abandoning the `CmmSink` improvements, once you figure out what is going on. If meanwhile you want to re-apply, and make the smaller change you propose, that's fine with me Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:53 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8834: 64-bit windows cabal.exe segfaults in GC ----------------------------------+---------------------------------- Reporter: awson | Owner: jstolarek 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 awson): Replying to [comment:52 jstolarek]:
According to my experiments you can fix Windows build easily by changing definition of `isTrivial` in !CmmSink to:
{{{ isTrivial :: CmmExpr -> Bool isTrivial (CmmReg (CmmLocal _)) = True isTrivial (CmmLit _) = True isTrivial _ = False }}}
Hmm, on my experiments changing `isTrivial` to {{{ isTrivial :: CmmExpr -> Bool isTrivial (CmmReg (CmmLocal _)) = True -- isTrivial (CmmLit _) = True isTrivial _ = False }}} alone was not enough to fix things - see my comment 19. So doing `CmmLit` branch `True` makes this work? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:54 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8834: 64-bit windows cabal.exe segfaults in GC ----------------------------------+---------------------------------- Reporter: awson | Owner: jstolarek 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): Here's a quick summary of what I've learned: * As we noticed earlier the bug does not happen when only `-O1` is used. Enabling `-O1 -fspec-constr` triggers the bug, but with `-O1 -fspec-constr -fno-cmm-sink` everything works perfectly fine. * I believe that Simon Marlow correctly identified offending piece of Cmm code, although my knowledge of calling conventions doesn't allow me to say why that piece of code is incorrect. Here's how that piece of code looks only with `-O1`: {{{ c2h9: _s2cz::I64 = _s2ct::I64 + _s2cv::I64; (_s2cE::I64) = call "ccall" arg hints: [PtrHint, `signed',] result hints: [PtrHint] memchr(_s2cz::I64, 10, _s2cw::I64); if (_s2cE::I64 == 0) goto c2h4; else goto c2h5; c2h4: Hp = Hp - 32; _s2cH::P64 = Data.Maybe.Nothing_closure+1; goto s2cF; c2h5: I64[Hp - 24] = GHC.Types.I#_con_info; I64[Hp - 16] = _s2cE::I64 - _s2cz::I64; I64[Hp - 8] = Data.Maybe.Just_con_info; P64[Hp] = Hp - 23; _s2cH::P64 = Hp - 6; goto s2cF; s2cF: call MO_Touch(_s2cu::P64); I64[Sp - 40] = c2f7; R1 = _s2cH::P64; I64[Sp - 32] = _s2ct::I64; P64[Sp - 24] = _s2cu::P64; I64[Sp - 16] = _s2cv::I64; I64[Sp - 8] = _s2cw::I64; Sp = Sp - 40; if (R1 & 7 != 0) goto c2f7; else goto c2f8; }}} It looks that sinking is not performed here for some reason that I was unable to figure out. Enabling `-O1 -fspec-constr` changes the above code to: {{{ c2hi: _s2dr::I64 = R5; _s2du::I64 = R2 + R4; _c2fB::I64 = R5; (_s2dz::I64) = call "ccall" arg hints: [PtrHint, `signed',] result hints: [PtrHint] memchr(_s2du::I64, 10, _c2fB::I64); if (_s2dz::I64 == 0) goto c2hd; else goto c2he; c2hd: call MO_Touch(R3); I64[Hp - 128] = Data.ByteString.Internal.PS_con_info; P64[Hp - 120] = R3; I64[Hp - 112] = R2; I64[Hp - 104] = R4; I64[Hp - 96] = _s2dr::I64; I64[Hp - 88] = :_con_info; P64[Hp - 80] = Hp - 127; P64[Hp - 72] = GHC.Types.[]_closure+1; _c2h8::P64 = Hp - 86; Hp = Hp - 72; R1 = _c2h8::P64; call (P64[Sp])(R1) args: 8, res: 0, upd: 8; }}} Enabling `-fspec-constr` sinks R2, R3 and R4 past the call to `memchr` (which BTW. is consistent with awson's earlier observation that segfault is happening somewhere around the call to `memchr`). * Changing definition of `isTrivial` from: {{{ isTrivial :: CmmExpr -> Bool isTrivial (CmmReg _) = True isTrivial (CmmLit _) = True isTrivial _ = False }}} to {{{ isTrivial :: CmmExpr -> Bool isTrivial (CmmReg (CmmLocal _)) = True isTrivial (CmmLit _) = True isTrivial _ = False }}} makes the bug disappear. I believe this is not a proper fix, because it only hides the bug - global registers should be safe to inline! The above Cmm code changes to (`-O1 -fspec-constr` enabled): {{{ 2hi: _s2du::I64 = _s2do::I64 + _s2dq::I64; (_s2dz::I64) = call "ccall" arg hints: [PtrHint, `signed',] result hints: [PtrHint] memchr(_s2du::I64, 10, _s2dr::I64); if (_s2dz::I64 == 0) goto c2hd; else goto c2he; 2hd: call MO_Touch(_s2dp::P64); I64[Hp - 128] = Data.ByteString.Internal.PS_con_info; P64[Hp - 120] = _s2dp::P64; I64[Hp - 112] = _s2do::I64; I64[Hp - 104] = _s2dq::I64; I64[Hp - 96] = _s2dr::I64; I64[Hp - 88] = :_con_info; P64[Hp - 80] = Hp - 127; P64[Hp - 72] = GHC.Types.[]_closure+1; _c2h8::P64 = Hp - 86; Hp = Hp - 72; R1 = _c2h8::P64; call (P64[Sp])(R1) args: 8, res: 0, upd: 8; }}} * Since it looks like the problem is caused by sinking registers past the unsafe foreign call to `memchr` I changed the definition of `foreignTargetRegs` in the instance definition of `DefinerOfRegs` in `CmmNode` (lines 345-346) from: {{{ foreignTargetRegs (ForeignTarget _ (ForeignConvention _ _ _ CmmNeverReturns)) = [] foreignTargetRegs _ = activeCallerSavesRegs }}} to: {{{ foreignTargetRegs (ForeignTarget _ (ForeignConvention _ _ _ CmmNeverReturns)) = [] foreignTargetRegs _ = activeRegs }}} This says that any global register can be clobbered by unsafe foreign call, in practice preventing any global register sinking past such calls. After this change the Cmm dump looks like this (again, `-O1 -fspec-constr` enabled): {{{ c2hi: _s2dr::I64 = R5; _s2dq::I64 = R4; _s2dp::P64 = R3; _s2do::I64 = R2; _s2du::I64 = R2 + R4; _c2fB::I64 = R5; (_s2dz::I64) = call "ccall" arg hints: [PtrHint, `signed',] result hints: [PtrHint] memchr(_s2du::I64, 10, _c2fB::I64); if (_s2dz::I64 == 0) goto c2hd; else goto c2he; c2hd: call MO_Touch(_s2dp::P64); I64[Hp - 128] = Data.ByteString.Internal.PS_con_info; P64[Hp - 120] = _s2dp::P64; I64[Hp - 112] = _s2do::I64; I64[Hp - 104] = _s2dq::I64; I64[Hp - 96] = _s2dr::I64; I64[Hp - 88] = :_con_info; P64[Hp - 80] = Hp - 127; P64[Hp - 72] = GHC.Types.[]_closure+1; _c2h8::P64 = Hp - 86; Hp = Hp - 72; R1 = _c2h8::P64; call (P64[Sp])(R1) args: 8, res: 0, upd: 8; }}} Based on above facts I believe that the problem lies in incorrect definition of caller saves registers. On the other hand I believe we are defining R2, R3 and R4 as callee-saves according to the specification. So there is still possibility that the bug lies somewhere else. At this point I am stuck. I will attach Cmm dumps in a moment so others can verify my findings. All dumps are for the `BugIso` module - they don't include boilerplate from `Main`. Replying to [comment:54 awson]:
Hmm, on my experiments changing `isTrivial` to {{{ isTrivial :: CmmExpr -> Bool isTrivial (CmmReg (CmmLocal _)) = True -- isTrivial (CmmLit _) = True isTrivial _ = False }}} alone was not enough to fix things - see my comment 19. So doing `CmmLit` branch `True` makes this work?
On my experiments the change of `isTrivial` that you just posted is enough to prevent the segmentation fault. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:55 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8834: 64-bit windows cabal.exe segfaults in GC ----------------------------------+---------------------------------- Reporter: awson | Owner: jstolarek 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 simonpj): Interesting; good progress. * Can you (by experiment) find which of registers is causing the problem. You fixed it by making them ''all'' caller saves, but that might be more than what's needed. * You say "It looks that sinking is not performed here for some reason that I was unable to figure out". I suspect it'd really be worth figuring this out. Maybe it's important! * You hypothesise that the C procedure `memchr` is destroying a callee- saves register. Might it be possible to test this hypothesis directly? For example, make the Haskell code call `my_memchr` instead, and handwrite `my_memchr` in assembly code, so that it saves all the registers (in a static location), calls the real `memchr`, and then checks whether the registers have changed. That would absolutely confirm that a claimed callee-saves register is being destroyed. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:56 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

* Can you (by experiment) find which of registers is causing the
#8834: 64-bit windows cabal.exe segfaults in GC ----------------------------------+---------------------------------- Reporter: awson | Owner: jstolarek 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): Replying to [comment:56 simonpj]: problem? You fixed it by making them ''all'' caller saves, but that might be more than what's needed.
* You hypothesise that the C procedure `memchr` is destroying a callee-
saves register. Might it be possible to test this hypothesis directly?
I looked at the implementation of `memchr` in `glibc` and it looks that on
64 bits it is touching `%rsi` and `%rdi` registers (our R3 and R4,
respectively). I changed this definition in
[[GhcFile(includes/stg/MachRegs.h)]]:
{{{
#if !defined(mingw32_HOST_OS)
#define CALLER_SAVES_R3
#define CALLER_SAVES_R4
#endif
}}}
to:
{{{
#define CALLER_SAVES_R3
#define CALLER_SAVES_R4
}}}
(ie. I removed the conditional) and the segfault has disappeared. Looking
at the Cmm confirms that R3 are R4 are now not sunk past the call to
`memchr`:
{{{
c2hy:
_s2dH::I64 = R5;
_s2dG::I64 = R4;
_s2dF::P64 = R3;
_s2dK::I64 = R2 + R4;
_c2fR::I64 = R5;
(_s2dP::I64) = call "ccall" arg hints: [PtrHint,
`signed',] result hints:
[PtrHint] memchr(_s2dK::I64, 10, _c2fR::I64);
if (_s2dP::I64 == 0) goto c2ht; else goto c2hu;
c2ht:
call MO_Touch(_s2dF::P64);
I64[Hp - 128] = Data.ByteString.Internal.PS_con_info;
P64[Hp - 120] = _s2dF::P64;
I64[Hp - 112] = R2;
I64[Hp - 104] = _s2dG::I64;
I64[Hp - 96] = _s2dH::I64;
I64[Hp - 88] = :_con_info;
P64[Hp - 80] = Hp - 127;
P64[Hp - 72] = GHC.Types.[]_closure+1;
_c2ho::P64 = Hp - 86;
Hp = Hp - 72;
R1 = _c2ho::P64;
}}}
But one thing is not right here:
{{{
#if !defined(mingw32_HOST_OS)
#define CALLER_SAVES_R3
#define CALLER_SAVES_R4
#endif
}}}
Under 64 bit Windows `mingw32_HOST_OS` should not be declared and
therefore R3 and R4 should be defined as caller saves! As a quick sanity
check I wrote this small C program and compiled it with the in-tree mingw
gcc:
{{{
#include

#8834: 64-bit windows cabal.exe segfaults in GC ----------------------------------+---------------------------------- Reporter: awson | Owner: jstolarek 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 simonmar): I believe `mingw32_HOST_OS` is defined on 64-bit Windows. The full platform name is `x86_64-unknown-mingw32`, i.e. `mingw32` is the OS. You can test this with `ghc --info` on your 64-bit Windows GHC. If `memchr` is clobbering allegedly callee-saves registers, then either `memchr` is wrong, or our idea of what is callee-saves is wrong. Which is it? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:58 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8834: 64-bit windows cabal.exe segfaults in GC ----------------------------------+---------------------------------- Reporter: awson | Owner: jstolarek 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 awson): `glibc` is completely irrelevant here. `memchr` comes from system dll `msvcrt.dll` and I doubt it is wrong. So, perhaps, our idea of what is callee-saves is wrong. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:59 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8834: 64-bit windows cabal.exe segfaults in GC ----------------------------------+---------------------------------- Reporter: awson | Owner: jstolarek 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): Replying to [comment:58 simonmar]:
I believe `mingw32_HOST_OS` is defined on 64-bit Windows. Doesn't the output from my small C program suggest otherwise? Am I missing something here?
You can test this with `ghc --info` on your 64-bit Windows GHC. {{{ (...) ,("target os","OSMinGW32") ,("target arch","ArchX86_64") (...) ,("Build platform","x86_64-unknown-mingw32") ,("Host platform","x86_64-unknown-mingw32") ,("Target platform","x86_64-unknown-mingw32") (...) }}}
glibc is completely irrelevant here. memchr comes from system dll msvcrt.dll and I doubt it is wrong.
Hmm... I doubt we can take a look at source of that dll ;-) awson, could you verify that change in `MachRegs.h` fixes the bug? You might need to recompile GHC from scratch, at least I had to do so because the changes weren't picked up after partial recompilation. Note: don't test that with latest HEAD as it contains Simon's temporary fix based on your earlier patch. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:60 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8834: 64-bit windows cabal.exe segfaults in GC ----------------------------------+---------------------------------- Reporter: awson | Owner: jstolarek 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 refold): Replying to [comment:60 jstolarek]:
glibc is completely irrelevant here. memchr comes from system dll msvcrt.dll and I doubt it is wrong.
Hmm... I doubt we can take a look at source of that dll ;-)
I believe that Microsoft ships the CRT source with Visual Studio. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:61 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8834: 64-bit windows cabal.exe segfaults in GC ----------------------------------+---------------------------------- Reporter: awson | Owner: jstolarek 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 simonpj): Austin will try: * Re-applying the `CmmSink` patch * Adding R3 and R4 to the caller-saves register for 64-bit That would be a better fix, because if they really are caller-saves then reverting `CmmSink` won't necessarily cure everything. Still needs more investigation for the ultimate cause. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:62 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8834: 64-bit windows cabal.exe segfaults in GC ----------------------------------+---------------------------------- Reporter: awson | Owner: jstolarek 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): Replying to [comment:61 refold]:
Replying to [comment:60 jstolarek]:
glibc is completely irrelevant here. memchr comes from system dll msvcrt.dll and I doubt it is wrong.
Hmm... I doubt we can take a look at source of that dll ;-)
I believe that Microsoft ships the CRT source with Visual Studio.
Great. Does anyone have access to Visual Studio and could check the implementation of `memchr`? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:63 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8834: 64-bit windows cabal.exe segfaults in GC
----------------------------------+----------------------------------
Reporter: awson | Owner: jstolarek
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 awson):
`memchr` implemented in C and I think MS' own C compiler is right. At
least `memchr` extracted from static counterpart of `msvcrt` is good:
{{{
test %r8,%r8
je 11

#8834: 64-bit windows cabal.exe segfaults in GC ----------------------------------+---------------------------------- Reporter: awson | Owner: jstolarek 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 igloo): http://msdn.microsoft.com/en-us/library/6t169e9c.aspx says {{{ The registers RAX, RCX, RDX, R8, R9, R10, R11 are considered volatile and must be considered destroyed on function calls (unless otherwise safety- provable by analysis such as whole program optimization). The registers RBX, RBP, RDI, RSI, RSP, R12, R13, R14, and R15 are considered nonvolatile and must be saved and restored by a function that uses them. }}} so the saving info looks right to me. It wouldn't be too surprising if saving and restoring registers more worked around a register corruption bug. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:65 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8834: 64-bit windows cabal.exe segfaults in GC ----------------------------------+---------------------------------- Reporter: awson | Owner: Type: bug | Status: new 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: ----------------------------------+---------------------------------- Changes (by thoughtpolice): * owner: jstolarek => * status: patch => new -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:66 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8834: 64-bit windows cabal.exe segfaults in GC ----------------------------------+---------------------------------- Reporter: awson | Owner: jstolarek Type: bug | Status: new 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: ----------------------------------+---------------------------------- Changes (by thoughtpolice): * owner: => jstolarek -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:67 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8834: 64-bit windows cabal.exe segfaults in GC ----------------------------------+---------------------------------- Reporter: awson | Owner: jstolarek Type: bug | Status: new Priority: high | Milestone: 7.8.2 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: ----------------------------------+---------------------------------- Changes (by thoughtpolice): * priority: highest => high * milestone: 7.8.1 => 7.8.2 Comment: This is now fixed in the 7.8 branch, so I'm moving this to 7.8.2 tentatively. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:68 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8834: 64-bit windows cabal.exe segfaults in GC ----------------------------------+---------------------------------- Reporter: awson | Owner: jstolarek Type: bug | Status: new Priority: high | Milestone: 7.8.2 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 simonmar): Hold the release! I've found the bug. It's in the native codegen. Patch coming soon. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:69 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8834: 64-bit windows cabal.exe segfaults in GC ----------------------------------+---------------------------------- Reporter: awson | Owner: jstolarek Type: bug | Status: new 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: ----------------------------------+---------------------------------- Changes (by simonmar): * priority: high => highest * milestone: 7.8.2 => 7.8.1 Comment: Patch attached. I'll validate it, but I only have one Windows laptop and I'm using it for work, so this might take a while. If someone else can validate more quickly, please go ahead. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:70 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8834: 64-bit windows cabal.exe segfaults in GC ----------------------------------+---------------------------------- Reporter: awson | Owner: jstolarek Type: bug | Status: new 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 simonmar): Oh, and you also have to revert a79613a75c7da0d3d225850382f0f578a07113b5 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:71 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8834: 64-bit windows cabal.exe segfaults in GC ----------------------------------+---------------------------------- Reporter: awson | Owner: jstolarek Type: bug | Status: new 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 awson): On the first glance patch looks slightly insufficient because it does not touch 32-bit case. Or did I missed something here? AFAIR, that also was the case of 32-bit GHC segfaults. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:72 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8834: 64-bit windows cabal.exe segfaults in GC ----------------------------------+---------------------------------- Reporter: awson | Owner: jstolarek Type: bug | Status: new 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 simonmar): Yeah, this is definitely the cause of the crash on 64-bit Windows, so if 32-bit is also crashing then there must be another bug somewhere. @thoughtpolice is going to test again and see if it's still crashing. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:73 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8834: 64-bit windows cabal.exe segfaults in GC ----------------------------------+---------------------------------- Reporter: awson | Owner: Type: bug | Status: new 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: ----------------------------------+---------------------------------- Changes (by jstolarek): * owner: jstolarek => -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:74 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8834: 64-bit windows cabal.exe segfaults in GC
----------------------------------+----------------------------------
Reporter: awson | Owner:
Type: bug | Status: new
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 Austin Seipp

#8834: 64-bit windows cabal.exe segfaults in GC ----------------------------------+---------------------------------- Reporter: awson | Owner: Type: bug | Status: new 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 thoughtpolice): Simon's patch works on x86_64 windows, with or without SPJ's temporary workaround committed. Cabal works properly. The testsuite looks quite clean modulo some perf numbers. Looks good! So I think technically this bug is fixed. But there's still an alleged 32bit error somewhere that Ganesh had, and Simon also had. I've had reports of Windows 7 being problematic in particular, so I'm looking to reproduce it right now with my build. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:76 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8834: 64-bit windows cabal.exe segfaults in GC ----------------------------------+---------------------------------- Reporter: awson | Owner: Type: bug | Status: new 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 thoughtpolice): I've definitely managed to reproduce this finally after a bunch of hunting - it doesn't really seem related to OS version, JUST related to MSYS2. #8870 is the same thing, I'm quite certain (failure at `CPSZ` output during segfault if you check `-v3`). It just doesn't make sense to me why the testsuite runs clean on my machine where I built the bindist, and everything works and compiles, but it fails for users and here. I'm running the testsuite right now and I can see some isolated failures that I'm quite sure are illegitimate (several segfaults), i'll report the results here, `./validate` is about half done. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:77 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8834: 64-bit windows cabal.exe segfaults in GC ----------------------------------+---------------------------------- Reporter: awson | Owner: Type: bug | Status: new 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 thoughtpolice): I see no actual suspicious testsuite failures (even in `codeGen`) that indicate anything is wrong - the only failures I get are due to the compiler itself segfaulting on a test. More soon. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:78 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8834: 64-bit windows cabal.exe segfaults in GC
----------------------------------+----------------------------------
Reporter: awson | Owner:
Type: bug | Status: new
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 thoughtpolice):
Okay, I spent some time boiling some things down, and I've at least
determined the approximate location of the segfault in the code during
compilation, which is `stmtToInstrs` in
`compiler/nativeGen/X86/CodeGen.hs`. Here's just a quick dump (to not
loose findings) and I'll keep looking around.
The fault is when compiling `System.Time` in profiling. Run under gdb:
{{{
$ gdb --args "inplace/bin/ghc-stage2.exe" -v3 -hisuf p_hi -osuf p_o
-hcsuf p_hc -static -prof -H32m -O -package-name old-time-1.i
-ilibraries/old-time/. -ilibraries/old-time/dist-install/build -ilibraries
/old-time/dist-install/build/autogen -Ilibraries/old-timearies/old-time
/dist-install/build/autogen -Ilibraries/old-time/include -optP-include
-optPlibraries/old-time/dist-install/build/auage base-4.7.0.0 -package
old-locale-1.0.0.6 -Wall -XHaskell2010 -O2 -no-user-package-db -rtsopts
-odir libraries/old-time/distaries/old-time/dist-install/build -stubdir
libraries/old-time/dist-install/build -c libraries/old-time/dist-
install/build/System/Tie/dist-install/build/System/Time.p_o +RTS -DS
GNU gdb (GDB) 7.6.1
Copyright (C) 2013 Free Software Foundation, Inc.
License GPLv3+: GNU GPL version 3 or later
http://gnu.org/licenses/gpl.html
This is free software: you are free to change and redistribute it.
There is NO WARRANTY, to the extent permitted by law. Type "show copying"
and "show warranty" for details.
This GDB was configured as "i686-pc-msys".
For bug reporting instructions, please see:
http://www.gnu.org/software/gdb/bugs/...
Traceback (most recent call last):
File "<string>", line 3, in <module>
ImportError: No module named libstdcxx.v6.printers
/etc/gdbinit:6: Error in sourced command file:
Error while executing Python code.
Reading symbols from /home/Administrator/ghc/inplace/bin/ghc-
stage2.exe...done.
warning: File "/home/Administrator/ghc/.gdbinit" auto-loading has been
declined by your `auto-load safe-path' set to "$debugdir:$datadir/auto-
load".
To enable execution of this file add
add-auto-load-safe-path /home/Administrator/ghc/.gdbinit
line to your configuration file "/home/Administrator/.gdbinit".
To completely disable this security protection add
set auto-load safe-path /
line to your configuration file "/home/Administrator/.gdbinit".
For more information about this security protection see the
"Auto-loading safe path" section in the GDB manual. E.g., run from the
shell:
info "(gdb)Auto-loading safe path"
(gdb) load .gdbinit
You can't do that when your target is `exec'
(gdb) source .gdbinit
(gdb) r
Starting program: /home/Administrator/ghc/inplace/bin/ghc-stage2.exe -v3
-hisuf p_hi -osuf p_o -hcsuf p_hc -static -prof -H32m -O -package-name
old-time-1.1.0.2 -hide-all-packages -i -ilibraries/old-time/. -ilibraries
/old-time/dist-install/build -ilibraries/old-time/dist-
install/build/autogen -Ilibraries/old-time/dist-install/build -Ilibraries
/old-time/dist-install/build/autogen -Ilibraries/old-time/include -optP-
include -optPlibraries/old-time/dist-install/build/autogen/cabal_macros.h
-package base-4.7.0.0 -package old-locale-1.0.0.6 -Wall -XHaskell2010 -O2
-no-user-package-db -rtsopts -odir libraries/old-time/dist-install/build
-hidir libraries/old-time/dist-install/build -stubdir libraries/old-time
/dist-install/build -c libraries/old-time/dist-
install/build/System/Time.hs -o libraries/old-time/dist-
install/build/System/Time.p_o +RTS -DS
[New Thread 1136.0xcc8]
cc8: cap 0: initialised
[New Thread 1136.0x15e8]
[New Thread 1136.0x1658]
[New Thread 1136.0x11b8]
[New Thread 1136.0x11e8]
[New Thread 1136.0x1718]
Glasgow Haskell Compiler, Version 7.9.20140329, stage 2 booted by GHC
version 7.6.3
Using binary package database:
C:\Users\Administrator\Desktop\msys32\home\Administrator\ghc\inplace\lib\package.conf.d\package.cache
wired-in package ghc-prim mapped to ghc-prim-0.3.1.0-inplace
wired-in package integer-gmp mapped to integer-gmp-0.5.1.0-inplace
wired-in package base mapped to base-4.7.0.0-inplace
wired-in package rts mapped to builtin_rts
wired-in package template-haskell mapped to template-
haskell-2.10.0.0-inplace
wired-in package dph-seq not found.
wired-in package dph-par not found.
Hsc static flags:
*** Checking old interface for old-time-1.1.0.2:System.Time:
*** Parser:
*** Renamer/typechecker:
*** Desugar:
Result size of Desugar (after optimization)
= {terms: 5,701, types: 3,843, coercions: 29}
...
*** Tidy Core:
Result size of Tidy Core
= {terms: 15,413, types: 10,079, coercions: 582}
Created temporary directory:
C:\Users\Administrator\Desktop\msys32\tmp\ghc1136_0
*** CorePrep:
Result size of CorePrep
= {terms: 18,936, types: 12,028, coercions: 582}
*** Stg2Stg:
*** CodeOutput:
*** New CodeGen:
*** CPSZ:
*** CPSZ:
*** CPSZ:
*** CPSZ:
*** CPSZ:
Program received signal SIGSEGV, Segmentation fault.
0x02137032 in c1hhA_info ()
(gdb) bt
#0 0x02137032 in c1hhA_info ()
Cannot access memory at address 0x28a874
(gdb) disassemble
Dump of assembler code for function c1hhA_info:
0x02137024 <+0>: sub $0x3510,%esp
0x0213702a <+6>: mov 0x8(%ebp),%eax
0x0213702d <+9>: mov 0x4(%ebp),%ecx
0x02137030 <+12>: mov %esi,%edx
=> 0x02137032 <+14>: mov %eax,0x184(%esp)
0x02137039 <+21>: mov -0x1(%edx),%eax
0x0213703c <+24>: movzwl -0x2(%eax),%eax
0x02137040 <+28>: cmp $0x1e,%eax
0x02137043 <+31>: ja 0x214916f

#8834: 64-bit windows cabal.exe segfaults in GC ----------------------------------+---------------------------------- Reporter: awson | Owner: Type: bug | Status: new 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 thoughtpolice): I'll also note that it seems turning off the sinking pass seems to make no difference (that is, `-fno-cmm-sink` in `compiler/nativeGen/X86/CodeGen.hs`) to cause this bug to still trigger, although I haven't verified it faults in exactly the same spot. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:80 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8834: 64-bit windows cabal.exe segfaults in GC ----------------------------------+---------------------------------- Reporter: awson | Owner: Type: bug | Status: new 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 thoughtpolice): The only way I can get this to *not* segfault is if I completely disable optimization with `{-# OPTIONS_GHC -O0 #-}` in `CodeGen.hs`. I'm going to see if the build completes and run the testsuite again to see what it says... (BTW, this is a typical performance build, so everything will be compiled with -O, at least). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:81 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8834: 64-bit windows cabal.exe segfaults in GC ----------------------------------+---------------------------------- Reporter: awson | Owner: Type: bug | Status: new 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 simonmar): {{{ 0x02137024 <+0>: sub $0x3510,%esp 0x0213702a <+6>: mov 0x8(%ebp),%eax 0x0213702d <+9>: mov 0x4(%ebp),%ecx 0x02137030 <+12>: mov %esi,%edx => 0x02137032 <+14>: mov %eax,0x184(%esp) }}} Oh wow, this function needs a *lot* of spill space on the C stack. I bet the problem is that we're bumping `%esp` by more than one page, and Windows doesn't like that, it expect the stack to grow by one page at a time. So the fix would be to write to the intervening pages one at a time. This is another bug in the NCG. I'm also interested in why this function needs quite so much extra stack. (also, shouldn't we be discussing this on #8870? The bug in this ticket is fixed, I think). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:82 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8834: 64-bit windows cabal.exe segfaults in GC ----------------------------------+---------------------------------- Reporter: awson | Owner: Type: bug | Status: closed Priority: highest | Milestone: 7.8.1 Component: Compiler | Version: 7.8.1-rc2 Resolution: fixed | Keywords: Operating System: Windows | Architecture: x86_64 (amd64) Type of failure: Runtime crash | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: ----------------------------------+---------------------------------- Changes (by thoughtpolice): * status: new => closed * resolution: => fixed Comment: Whoops, yes, this is fixed. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:83 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8834: 64-bit windows cabal.exe segfaults in GC ----------------------------------+---------------------------------- Reporter: awson | Owner: Type: bug | Status: closed Priority: highest | Milestone: 7.8.1 Component: Compiler | Version: 7.8.1-rc2 Resolution: fixed | Keywords: Operating System: Windows | Architecture: x86_64 (amd64) Type of failure: Runtime crash | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: ----------------------------------+---------------------------------- Comment (by awson): Now, when #8870 looks understood can we revert [https://ghc.haskell.org/trac/ghc/changeset/a79613a75c7da0d3d225850382f0f578a... a79613a75c7da0d3d225850382f0f578a07113b5]? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8834#comment:84 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8834: 64-bit windows cabal.exe segfaults in GC
----------------------------------+----------------------------------
Reporter: awson | Owner:
Type: bug | Status: closed
Priority: highest | Milestone: 7.8.1
Component: Compiler | Version: 7.8.1-rc2
Resolution: fixed | Keywords:
Operating System: Windows | Architecture: x86_64 (amd64)
Type of failure: Runtime crash | Difficulty: Unknown
Test Case: | Blocked By:
Blocking: | Related Tickets:
----------------------------------+----------------------------------
Comment (by Austin Seipp
participants (1)
-
GHC