[GHC] #12031: GHCi segfaults on Windows when compiling C code using extern-declared variable

#12031: GHCi segfaults on Windows when compiling C code using extern-declared
variable
----------------------------------------+-------------------------------
Reporter: RyanGlScott | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: GHCi | Version: 8.0.1
Keywords: | Operating System: Windows
Architecture: Unknown/Multiple | Type of failure: GHCi crash
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
----------------------------------------+-------------------------------
Phyx- and I [https://phabricator.haskell.org/D1805#59850 noticed] that
`bindings-GLFW` unpredictably segfaults when running this simple program
in interpreted code:
{{{#!hs
module Main where
import qualified Graphics.UI.GLFW as G
main :: IO ()
main = do
successfulInit <- G.init
return ()
}}}
Phyx- [https://phabricator.haskell.org/D1805#60275 suspected] that it had
something to do with the `extern`-declared variables used in the GLFW
library itself. To avoid requiring a dependency on GLFW, I boiled the
issue down to a small, reproducible example with no dependencies, located
at https://github.com/RyanGlScott/extern-bug. I will reproduce the code
below:
{{{#!c
// foo.h
#ifndef FOO_H
#define FOO_H
extern int foo;
void bar(void);
void baz(void);
#endif
}}}
{{{#!c
// bar.c
#include "foo.h"
int foo = 0;
void bar(void) {
foo = 1;
baz();
}
}}}
{{{#!c
// baz.c
#include "foo.h"
#include

#12031: GHCi segfaults on Windows when compiling C code using extern-declared variable --------------------------------+---------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.1 Resolution: | Keywords: Operating System: Windows | Architecture: Unknown/Multiple Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | --------------------------------+---------------------------------------- Comment (by RyanGlScott): I can't reproduce this issue with GHC 7.8.4 or 7.10.2, so it looks like the problem surfaced in GHC 7.10.3. Perhaps [https://ghc.haskell.org/trac/ghc/ticket/10726 upgrading the MinGW-w64 toolchain] has something to do with this? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12031#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12031: GHCi segfaults on Windows when compiling C code using extern-declared
variable
--------------------------------+----------------------------------------
Reporter: RyanGlScott | Owner: Phyx-
Type: bug | Status: new
Priority: normal | Milestone:
Component: GHCi | Version: 8.0.1
Resolution: | Keywords:
Operating System: Windows | Architecture: Unknown/Multiple
Type of failure: GHCi crash | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
--------------------------------+----------------------------------------
Changes (by Phyx-):
* owner: => Phyx-
Comment:
Thanks for the simplified example @RyanGlScott. It made it a lot easier to
find.
This seems like it has to do with MingW-w64's pseudo-relocation features.
The references to the `foo` extern value seems to go through a `.refptr`
reference.
The values to jump to are contained in their own `$rdata` section such as
{{{
Disassembly of section .rdata$.refptr.foo:
0000000000000000 <.refptr.foo>:
...
0: R_X86_64_64 foo
}}}
Which contains the address of `foo`. It seems that this is done to take
advantage of the
full 48-bit address space for x64 Windows. This because the instruction
relocations are done
in 32-bit space. e.g. using R_X86_64_PC32.
Looking at the dissassembly of `baz.c` you see that the direct lookup of
`foo` has been replaced.
{{{
Disassembly of section .text:
0000000000000000 <baz>:
0: 55 push %rbp
1: 48 89 e5 mov %rsp,%rbp
4: 48 83 ec 20 sub $0x20,%rsp
8: 48 8b 05 00 00 00 00 mov 0x0(%rip),%rax # f

#12031: GHCi segfaults on Windows when compiling C code using extern-declared variable --------------------------------+---------------------------------------- Reporter: RyanGlScott | Owner: Phyx- Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.1 Resolution: | Keywords: Operating System: Windows | Architecture: Unknown/Multiple Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | --------------------------------+---------------------------------------- Comment (by Phyx-): To round up the issue, the reason this seems to go wrong is because of how we initialize the `.bss` section for Windows in the runtime linker. The first issue is where we calculate the zero space for the section: {{{ zspace = stgCallocBytes(1, bss_sz, "ocGetNames_PEi386(anonymous bss)"); sectab_i->PointerToRawData = ((UChar*)zspace) - ((UChar*)(oc->image)); }}} Where {{{ UInt32 PointerToRawData; }}} This means we're stuffing a `64-bit` value into a `32-bit` one. Also `zspace` can be larger than `oc->image`. In which case it'll overflow and then get truncated in the cast. The address of a value in the `.bss` section is then calculated as: {{{ addr = ((UChar*)(oc->image)) + (sectabent->PointerToRawData + symtab_i->Value); }}} If it does truncate then this calculation won't be correct (which is what is happening). We then later use the value of `addr` as the `S` (Symbol) value for the relocations {{{ S = (size_t) lookupSymbol_( (char*)symbol ); }}} Now the majority of the relocations are `R_X86_64_PC32` etc. e.g. They are guaranteed to fit in a `32-bit` value. The `R_X86_64_64` introduced for these pseudo-relocations so they can use the full `48-bit` addressing space isn't as lucky. As for why it sometimes work has to do on whether the value is truncated or not. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12031#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12031: GHCi segfaults on Windows when compiling C code using extern-declared variable -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Phyx- Type: bug | Status: new Priority: high | Milestone: 8.0.2 Component: Runtime System | Version: 8.0.1 (Linker) | Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 | (amd64) Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by Phyx-): * priority: normal => high * component: GHCi => Runtime System (Linker) * architecture: Unknown/Multiple => x86_64 (amd64) * milestone: => 8.0.2 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12031#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12031: GHCi segfaults on Windows when compiling C code using extern-declared variable -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Phyx- Type: bug | Status: patch Priority: high | Milestone: 8.0.2 Component: Runtime System | Version: 8.0.1 (Linker) | Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 | (amd64) Type of failure: GHCi crash | Test Case: T12031 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2316 Wiki Page: | -------------------------------------+------------------------------------- Changes (by Phyx-): * status: new => patch * testcase: => T12031 * differential: => Phab:D2316 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12031#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12031: GHCi segfaults on Windows when compiling C code using extern-declared
variable
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: Phyx-
Type: bug | Status: patch
Priority: high | Milestone: 8.0.2
Component: Runtime System | Version: 8.0.1
(Linker) |
Resolution: | Keywords:
Operating System: Windows | Architecture: x86_64
| (amd64)
Type of failure: GHCi crash | Test Case: T12031
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D2316
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Tamar Christina

#12031: GHCi segfaults on Windows when compiling C code using extern-declared variable -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Phyx- Type: bug | Status: merge Priority: high | Milestone: 8.0.2 Component: Runtime System | Version: 8.0.1 (Linker) | Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 | (amd64) Type of failure: GHCi crash | Test Case: T12031 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2316 Wiki Page: | -------------------------------------+------------------------------------- Changes (by Phyx-): * status: patch => merge -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12031#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12031: GHCi segfaults on Windows when compiling C code using extern-declared variable -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Phyx- Type: bug | Status: merge Priority: high | Milestone: 8.0.2 Component: Runtime System | Version: 8.0.1 (Linker) | Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 | (amd64) Type of failure: GHCi crash | Test Case: T12031 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2316 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Phyx, do you think you could rebase comment:6 onto the `ghc-8.0` branch? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12031#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12031: GHCi segfaults on Windows when compiling C code using extern-declared variable -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Phyx- Type: bug | Status: merge Priority: high | Milestone: 8.0.2 Component: Runtime System | Version: 8.0.1 (Linker) | Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 | (amd64) Type of failure: GHCi crash | Test Case: T12031 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2316 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Phyx-): @bgamari, Sure, no problem. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12031#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12031: GHCi segfaults on Windows when compiling C code using extern-declared variable -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Phyx- Type: bug | Status: merge Priority: high | Milestone: 8.0.2 Component: Runtime System | Version: 8.0.1 (Linker) | Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 | (amd64) Type of failure: GHCi crash | Test Case: T12031 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2316 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Phyx, I gave merging comment:6 a shot with 38497a2317b015249c96d03c2c3df97fffdc6929. It would be great if you could just test it. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12031#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12031: GHCi segfaults on Windows when compiling C code using extern-declared variable -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Phyx- Type: bug | Status: merge Priority: high | Milestone: 8.0.2 Component: Runtime System | Version: 8.0.1 (Linker) | Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 | (amd64) Type of failure: GHCi crash | Test Case: T12031 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2316 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Phyx-): @bgamari, you need to merge ae7e9cb574801954c7769c210829b06193fa72ea as well as this fixes the Ticky format specifiers. Currently that GHC-8.0 branch doesn't build with validate settings due to it. Also the following need to be applied {{{ diff --git a/rts/Linker.c b/rts/Linker.c index 8e00b92..82a37c8 100644 --- a/rts/Linker.c +++ b/rts/Linker.c @@ -4102,13 +4102,13 @@ ocGetNames_PEi386 ( ObjectCode* oc ) if (globalBssSize > 0) { bss = stgCallocBytes(1, globalBssSize, "ocGetNames_PEi386(non-anonymous bss)"); - addSection(§ions[oc->n_sections-1], + addSection(&oc->sections[oc->n_sections-1], SECTIONKIND_RWDATA, SECTION_MALLOC, bss, globalBssSize, 0, 0, 0); IF_DEBUG(linker, debugBelch("bss @ %p %" FMT_Word "\n", bss, globalBssSize)); addProddableBlock(oc, bss, globalBssSize); } else { - addSection(§ions[oc->n_sections-1], + addSection(&oc->sections[oc->n_sections-1], SECTIONKIND_OTHER, SECTION_NOMEM, NULL, 0, 0, 0, 0); } }}} This will make It compile, but the test isn't giving any output, have to look into that. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12031#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12031: GHCi segfaults on Windows when compiling C code using extern-declared variable -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Phyx- Type: bug | Status: merge Priority: high | Milestone: 8.0.2 Component: Runtime System | Version: 8.0.1 (Linker) | Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 | (amd64) Type of failure: GHCi crash | Test Case: T12031 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2316 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Phyx-): @bgamari, With those changes above it works. Test doesn't pass because ` TEST_HC_OPTS_INTERACTIVE` isn't defined in the teststuite of that version. If you want to make it pass, do: {{{ diff --git a/testsuite/tests/rts/T12031/Makefile b/testsuite/tests/rts/T12031/Makefile index 0a94206..72b34cc 100644 --- a/testsuite/tests/rts/T12031/Makefile +++ b/testsuite/tests/rts/T12031/Makefile @@ -5,4 +5,4 @@ include $(TOP)/mk/test.mk T12031: '$(TEST_HC)' -c bar.c -o bar.o '$(TEST_HC)' -c baz.c -o baz.o - echo bar | '$(TEST_HC)' $(TEST_HC_OPTS_INTERACTIVE) bar.o baz.o ExternBug.hs + echo bar | '$(TEST_HC)' $(TEST_HC_OPTS) --interactive -v0 -ignore- dot-ghci -fno-ghci-history bar.o baz.o ExternBug.hs }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12031#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12031: GHCi segfaults on Windows when compiling C code using extern-declared
variable
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: Phyx-
Type: bug | Status: merge
Priority: high | Milestone: 8.0.2
Component: Runtime System | Version: 8.0.1
(Linker) |
Resolution: | Keywords:
Operating System: Windows | Architecture: x86_64
| (amd64)
Type of failure: GHCi crash | Test Case: T12031
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D2316
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by thomie):
Perhaps apply this commit: bdc555885b8898684549eca70053c9ce0ec7fa39
{{{
Author: Thomas Miedema

#12031: GHCi segfaults on Windows when compiling C code using extern-declared variable -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Phyx- Type: bug | Status: closed Priority: high | Milestone: 8.0.2 Component: Runtime System | Version: 8.0.1 (Linker) | Resolution: fixed | Keywords: Operating System: Windows | Architecture: x86_64 | (amd64) Type of failure: GHCi crash | Test Case: T12031 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2316 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: I merged the definition suggested by thomie in comment:13 in 3308b30be6a5eef71039923e94f11d9809671ca2. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12031#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC