- 18 Jul, 2018 2 commits
-
-
Tamar Christina authored
Summary: On Windows one is not allowed to drop the stack by more than a page size. The reason for this is that the OS only allocates enough stack till what the TEB specifies. After that a guard page is placed and the rest of the virtual address space is unmapped. The intention is that doing stack allocations will cause you to hit the guard which will then map the next page in and move the guard. This is done to prevent what in the Linux world is known as stack clash vulnerabilities https://access.redhat.com/security/cve/cve-2017-1000364. There are modules in GHC for which the liveliness analysis thinks the reserved 8KB of spill slots isn't enough. One being DynFlags and the other being Cabal. Though I think the Cabal one is likely a bug: ``` 4d6544: 81 ec 00 46 00 00 sub $0x4600,%esp 4d654a: 8d 85 94 fe ff ff lea -0x16c(%ebp),%eax 4d6550: 3b 83 1c 03 00 00 cmp 0x31c(%ebx),%eax 4d6556: 0f 82 de 8d 02 00 jb 4ff33a <_cLpg_info+0x7a> 4d655c: c7 45 fc 14 3d 50 00 movl $0x503d14,-0x4(%ebp) 4d6563: 8b 75 0c mov 0xc(%ebp),%esi 4d6566: 83 c5 fc add $0xfffffffc,%ebp 4d6569: 66 f7 c6 03 00 test $0x3,%si 4d656e: 0f 85 a6 d7 02 00 jne 503d1a <_cLpb_info+0x6> 4d6574: 81 c4 00 46 00 00 add $0x4600,%esp ``` It allocates nearly 18KB of spill slots for a simple 4 line function and doesn't even use it. Note that this doesn't happen on x64 or when making a validate build. Only when making a build without a validate and build.mk. This and the allocation in DynFlags means the stack allocation will jump over the guard page into unmapped memory areas and GHC or an end program segfaults. The pagesize on x86 Windows is 4KB which means we hit it very easily for these two modules, which explains the total DOA of GHC 32bit for the past 3 releases and the "random" segfaults on Windows. ``` 0:000> bp 00503d29 0:000> gn Breakpoint 0 hit WARNING: Stack overflow detected. The unwound frames are extracted from outside normal stack bounds. eax=03b6b9c9 ebx=00dc90f0 ecx=03cac48c edx=03cac43d esi=03b6b9c9 edi=03abef40 eip=00503d29 esp=013e96fc ebp=03cf8f70 iopl=0 nv up ei pl nz na po nc cs=0023 ss=002b ds=002b es=002b fs=0053 gs=002b efl=00000202 setup+0x103d29: 00503d29 89442440 mov dword ptr [esp+40h],eax ss:002b:013e973c=???????? WARNING: Stack overflow detected. The unwound frames are extracted from outside normal stack bounds. WARNING: Stack overflow detected. The unwound frames are extracted from outside normal stack bounds. 0:000> !teb TEB at 00384000 ExceptionList: 013effcc StackBase: 013f0000 StackLimit: 013eb000 ``` This doesn't fix the liveliness analysis but does fix the allocations, by emitting a function call to `__chkstk_ms` when doing allocations of larger than a page, this will make sure the stack is probed every page so the kernel maps in the next page. `__chkstk_ms` is provided by `libGCC`, which is under the `GNU runtime exclusion license`, so it's safe to link against it, even for proprietary code. (Technically we already do since we link compiled C code in.) For allocations smaller than a page we drop the stack and probe the new address. This avoids the function call and still makes sure we hit the guard if needed. PS: In case anyone is Wondering why we didn't notice this before, it's because we only test x86_64 and on Windows 10. On x86_64 the page size is 8KB and also the kernel is a bit more lenient on Windows 10 in that it seems to catch the segfault and resize the stack if it was unmapped: ``` 0:000> t eax=03b6b9c9 ebx=00dc90f0 ecx=03cac48c edx=03cac43d esi=03b6b9c9 edi=03abef40 eip=00503d2d esp=013e96fc ebp=03cf8f70 iopl=0 nv up ei pl nz na po nc cs=0023 ss=002b ds=002b es=002b fs=0053 gs=002b efl=00000202 setup+0x103d2d: 00503d2d 8b461b mov eax,dword ptr [esi+1Bh] ds:002b:03b6b9e4=03cac431 0:000> !teb TEB at 00384000 ExceptionList: 013effcc StackBase: 013f0000 StackLimit: 013e9000 ``` Likely Windows 10 has a guard page larger than previous versions. This fixes the stack allocations, and as soon as I get the time I will look at the liveliness analysis. I find it highly unlikely that simple Cabal function requires ~2200 spill slots. Test Plan: ./validate Reviewers: simonmar, bgamari Reviewed By: bgamari Subscribers: AndreasK, rwbarton, thomie, carter GHC Trac Issues: #15154 Differential Revision: https://phabricator.haskell.org/D4917
-
Tamar Christina authored
Summary: Package registration does not seem to be thread-safe on Windows. Placing the system under heavily load seems to trigger registration failures even though they are all different package-dbs. This makes the plugin tests a bit flaky. I think this is because on Windows we use pessimistic locks while on Linux we use atomic file replacement. On Windows ReplaceFile is atomic, just the metadata write may not be. Since the metadata is not of importance we should either switch over to ReplaceFile or fix the locking code to not error out but wait. For now however I have to force these 25 tests to run serially in order to guarantee their correctness. Test Plan: ./validate Reviewers: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15313, #13194 Differential Revision: https://phabricator.haskell.org/D4918
-
- 17 Jul, 2018 7 commits
-
-
Sasa Bogicevic authored
Reviewers: bgamari, osa1 Reviewed By: osa1 Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15410 Differential Revision: https://phabricator.haskell.org/D4979
-
Sasa Bogicevic authored
Reviewers: bgamari, osa1 Reviewed By: osa1 Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15408 Differential Revision: https://phabricator.haskell.org/D4978
-
Sasa Bogicevic authored
Reviewers: goldfire, bgamari, osa1 Reviewed By: osa1 Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15407 Differential Revision: https://phabricator.haskell.org/D4977
-
Sasa Bogicevic authored
Reviewers: goldfire, bgamari, RyanGlScott Reviewed By: RyanGlScott Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15406 Differential Revision: https://phabricator.haskell.org/D4976
-
Sergei Trofimovich authored
Two minor changes: - 32-bit CPU macro is called riscv32_HOST_ARCH (was riscv_HOST_ARCH) - shrink understood tuples from riscv* to riscv-* and riscv32*-* as a tiny safeguard against riscv128*- in future. Suggested-by:
James Clarke <jrtc27@jrtc27.com> Signed-off-by:
Sergei Trofimovich <slyfox@gentoo.org>
-
Sasa Bogicevic authored
Reviewers: goldfire, bgamari, mpickering Reviewed By: mpickering Subscribers: mpickering, goldfire, rwbarton, thomie, carter GHC Trac Issues: #15405 Differential Revision: https://phabricator.haskell.org/D4975
-
Tamar Christina authored
A change has caused GHC to generate excessive specializations. This is making GHC generate 1800 splits for a simple GHC.Prim module, which means 1800 fork/exec calls. Due to this compilation times on Windows with split-objs on take over 24 hours to complete depending on your disk speed. Also the end compiler compiling medium to large project is also much slower. So I think we need to just disable split-objects. As there's nothing that can be done about this. Test Plan: ./validate Reviewers: bgamari Subscribers: tdammers, rwbarton, thomie, erikd, carter GHC Trac Issues: #15051 Differential Revision: https://phabricator.haskell.org/D4915
-
- 16 Jul, 2018 11 commits
-
-
Simon Marlow authored
* All the tests in tests/ghci.debugger now pass with -fexternal-interpreter. These tests are now run with the ghci-ext way in addition to the normal way so we won't break it in the future. * I removed all the unsafeCoerce# calls from RtClosureInspect. Yay! The main changes are: * New messages: GetClosure and Seq. GetClosure is a remote interface to GHC.Exts.Heap.getClosureData, which required Binary instances for various datatypes. Fortunately this wasn't too painful thanks to DeriveGeneric. * No cheating by unsafeCoercing values when printing them. Now we have to turn the Closure representation back into the native representation when printing Int, Float, Double, Integer and Char. Of these, Integer was the most painful - we now have a dependency on integer-gmp due to needing access to the representation. * Fixed a bug in rts/Heap.c - it was bogusly returning stack content as pointers for an AP_STACK closure. Test Plan: * `cd testsuite/tests/ghci.debugger && make` * validate Reviewers: bgamari, patrickdoc, nomeata, angerman, hvr, erikd, goldfire Subscribers: alpmestan, snowleopard, rwbarton, thomie, carter GHC Trac Issues: #13184 Differential Revision: https://phabricator.haskell.org/D4955
-
f-a authored
removed whitespace and added relevant imports to the "Memory Model" example (haddock documentation). Reviewers: hvr, bgamari Reviewed By: bgamari Subscribers: RyanGlScott, rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4966
-
Masahiro Sakai authored
Some hash signs in documents in primops.txt.pp were not escaped properly. Those raw hash signs were kept in haddock and texts between those hash signs were interpreted as anchors by haddock.
-
Simon Jakobi authored
-
Vladislav Zavialov authored
Implementation of the "Embrace TypeInType" proposal was done according to the spec, which specified that TypeOperators must imply NoStarIsType. This implication was meant to prevent breakage and to be removed in 2 releases. However, compiling head.hackage has shown that this implication only magnified the breakage, so there is no reason to have it in the first place. To remain in compliance with the three-release policy, we add a workaround to define the (*) type operator even when -XStarIsType is on. Test Plan: ./validate Reviewers: bgamari, RyanGlScott, goldfire, phadej, hvr Reviewed By: bgamari, RyanGlScott Subscribers: harpocrates, rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4865
-
Ryan Scott authored
Summary: The specification for the `S_TPush` rule in the core spec's operational semantics is woefully out-of-date. Let's bring it in line with the presentation in //System FC with Explicit Kind Equality//. Test Plan: Read it Reviewers: goldfire, bgamari Reviewed By: goldfire Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4970
-
Sergei Trofimovich authored
Tested on riscv64-unknown-linux-gnu tuple. Signed-off-by:
Sergei Trofimovich <slyfox@gentoo.org>
-
Sergei Trofimovich authored
Trac #15338 is yet another example where -Bsymbolic breaks semantics of a C program: global variable duplication happens and unsafePerformIO creates two stdout copies. When -Bsymbolic is not used both C compiler and linker agree on how global variables are handled. In case of sh4 it consists on a few assertions: 1. global variable is exported from shared library 2. code is referred to this variable via GOT-like mechanism to allow interposition 3. global variable is present .bss section on an executable (as an R_*_COPY relocation: symbol contents is copied at executable startup time) 4. and symbol in executable interposes symbol in shared library. This way both code in shared library and code in executable refer to a copy of global variable in .bss section of an executable. Unfortunately -Bsymbolic option breaks assumption [2.] and generates direct references to the symbol. This causes mismatch between values seen from executable and values seen from shared library code. This change disables '-Bsymbolic' for unregisterised targets. Signed-off-by:
Sergei Trofimovich <slyfox@gentoo.org> Test Plan: test 'ghc-pkg --version | cat' to emit data Reviewers: simonmar, bgamari, jrtc27 Reviewed By: jrtc27 Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15338 Differential Revision: https://phabricator.haskell.org/D4959
-
lantti authored
-
Simon Marlow authored
Summary: All these were detected by -fghci-leak-check when GHC was compiled *without* optimisation (e.g. using the "quick" build flavour). Unfortunately I don't know of a good way to keep this working. I'd like to just disable the -fghci-leak-check flag when the compiler is built without optimisation, but it doesn't look like we have an easy way to do that. And even if we could, it would be fragile anyway, Test Plan: `cd testsuite/tests/ghci; make` Reviewers: bgamari, hvr, erikd, tdammers Subscribers: tdammers, rwbarton, thomie, carter GHC Trac Issues: #15246 Differential Revision: https://phabricator.haskell.org/D4872
-
Ryan Scott authored
Summary: `core-spec.pdf` was emitting parse errors due to not specifying role arguments in some uses of `nth`. This patch adds those role arguments. (Credit goes to Richard Eisenberg for actually figuring out what said arguments should be.) Test Plan: Read it Reviewers: goldfire, bgamari Reviewed By: goldfire Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15373 Differential Revision: https://phabricator.haskell.org/D4965
-
- 15 Jul, 2018 9 commits
-
-
Alan Zimmerman authored
In the following data FieldOcc pass = FieldOcc { extFieldOcc :: XFieldOcc pass , rdrNameFieldOcc :: Located RdrName -- ^ See Note [Located RdrNames] in HsExpr } | XFieldOcc (XXFieldOcc pass) we are using XFieldOcc for both the extFieldOcc type and the extra constructor. The first one should be XCFieldOcc Updates haddock submodule closes #15386
-
David Feuer authored
Reviewers: simonmar, hvr, bgamari, erikd, fryguybob, rrnewton Reviewed By: simonmar Subscribers: fryguybob, rwbarton, thomie, carter GHC Trac Issues: #15364 Differential Revision: https://phabricator.haskell.org/D4884
-
Richard Eisenberg authored
There were some performance tests not classified by compiler_num_stats_field, causing erroneous failures when testing a DEBUG compiler. This fixes that oversight, addressing #15374.
-
Richard Eisenberg authored
The DEBUG compiler's GHCi still leaks. This commit suppresses testsuite failures due to this leak. See #15372.
-
Richard Eisenberg authored
A recent commit added extra calls to mkNakedCastTy to satisfy Note [The tcType invariant]. However, some of these casts were being applied to unsaturated type family applications, which caused ASSERTion failures in TcFlatten later on. This patch is more judicious in using mkNakedCastTy to avoid this problem.
-
Richard Eisenberg authored
Previously, this check was done in mkDataCon. But this sometimes caused assertion failures if an invalid data con was made. I've moved the check to checkValidDataCon, where we can be sure the datacon is otherwise valid first.
-
Richard Eisenberg authored
Several tests were failing in DEBUG mode, but fixing this was easy: just pass $(TEST_HC_OPTS) in the relevant Makefiles.
-
Richard Eisenberg authored
This removes an ASSERTion that TcLevels should increase by exactly one in every implication. While this is a sensible goal, it's not true today, and we should not be crippling DEBUG for everyone while debugging this. The ASSERT was added in 261dd83c
-
Simon Marlow authored
Avoids repeated wakeup messages being sent when a TVar is written to multiple times. See comments for details. Test Plan: * Test from #15136 (will be added to stm shortly) * existing stm tests Reviewers: bgamari, osa1, erikd Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15136 Differential Revision: https://phabricator.haskell.org/D4961
-
- 14 Jul, 2018 5 commits
-
-
Ben Gamari authored
I believe this was originally introduced to help test DPH, which is now gone.
-
Ben Gamari authored
-
Ben Gamari authored
-
Ben Gamari authored
-
Ben Gamari authored
-
- 13 Jul, 2018 6 commits
-
-
Simon Peyton Jones authored
-
Simon Marlow authored
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
A conversation with Richard made me look at floatEqualities again, and I did not find it easy to read. This patch refactors it sligtly, with better variable naming and more comments. I also fixed one latent bug, I think. In the old code, I think that an inhomogeneous or insoluble equality (co :: t1~t2), which doesn't float, and ended up in the badly-named 'non_eqs', would not end up in extended_skols. Hence it would not capture an equality that mentioned 'co' in a cast. It's still pretty horrible (as Richard and I have been discussing), but better. No change in behaviour; I don't know a program that would trigger the latent bug, even if my reasoning is right.
-
Ömer Sinan Ağacan authored
CONSTR_NOCAF was introduced with 55d535da as a replacement for CONSTR_STATIC and CONSTR_NOCAF_STATIC, however, as explained in Note [static constructors], we copy CONSTR_NOCAFs (which can also be seen in evacuate) during GC, and they can become dead, like other CONSTR_X_Ys. processHeapClosureForDead is updated to reflect this. Test Plan: Validates on x86_64. Existing failures on i386. Reviewers: simonmar, bgamari, erikd Reviewed By: simonmar, bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #7836, #15063, #15087, #15165 Differential Revision: https://phabricator.haskell.org/D4928
-
Simon Marlow authored
-