- Jul 27, 2018
-
-
We already include -haddock in the GhcLibHcOpts in order to include the boot libraries' docs in their .hi-files. By including -haddock in the GhcStage2HcOpts and GhcStage3HcOpts, we make the docs for the ghc library also available to the GHCi :doc command. Reviewers: bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4913
-
Without this change RTS typically doesn't flush some important events until the process terminates or it doesn't write them at all in case it terminates abnormally. Here is a list of such events: * EVENT_WALL_CLOCK_TIME * EVENT_OS_PROCESS_PID * EVENT_OS_PROCESS_PPID * EVENT_RTS_IDENTIFIER * EVENT_PROGRAM_ARGS * EVENT_PROGRAM_ENV
-
Ben Gamari authored
-
Simon Peyton Jones authored
In reviewing Phab:D4968 for Trac #15385 I saw a small but simple refactor to avoid unnecessary work in the desugarer. This patch just arranges to call matchSinglePatVar v ... rather than matchSinglePat (Var v) ... The more specialised function already existed, as match_single_pat_var I also added more comments about decideBangHood
-
Simon Peyton Jones authored
The constraint (~) used to be (effectively): class a ~~ b => (a :: k) ~ (b :: k) but, with this patch, it is now defined uniformly with (~~) and Coercible like this: class a ~# b => (a :: k) ~ (b :: k) Result: * One less superclass selection when goinng from (~) to (~#) Better for compile time and better for debugging with -ddump-simpl * The code for (~), (~~), and Coercible looks uniform, and appears together, e.g. in TysWiredIn and ClsInst.matchGlobalInst. Previously the code for (~) was different, and unique. Not only is this simpler, but it also makes the compiler a bit faster; T12227: 9% less allocation T12545: 7% less allocation This patch fixes Trac #15421
-
- Jul 25, 2018
-
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
As Trac #15436 points out, it is possible to get case dataToTag# (x :: T) of DEFAULT -> blah1 -1# -> blah2 0 -> blah3 The (-1#) alterantive is unreachable, because dataToTag# returns tags in the range [0..n-1] where n is the number of data constructors in type T. This actually made GHC crash; now we simply discard the unreachable alterantive. See Note [Unreachable caseRules alternatives] in PrelRules
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
The cloneWC, cloneWanted, cloneImplication family are used by * TcHoleErrors * TcRule to clone the /bindings/ in a constraint, so that solving the constraint will not add bindings to the program. The idea is only to affect unifications. But I had it wrong -- I failed to clone the EvBindsVar of an implication. That gave an assert failure, I think, as well as useless dead code. The fix is easy. I'm not adding a test case. In the type 'TcEvidence.EvBindsVar', I also renamed the 'NoEvBindsVar' constructor to 'CoEvBindsVar'. It's not that we have /no/ evidence bindings, just that we can only have coercion bindings, done via HoleDest.
-
Simon Peyton Jones authored
It turned out that we were not being consistent about our use of isConstraintKind. It's delicate, because the typechecker treats Constraint and Type as /distinct/, whereas they are the /same/ in the rest of the compiler (Trac #11715). And had it wrong, which led to Trac #15412. This patch does the following: * Rename isConstraintKind to tcIsConstraintKind returnsConstraintKind to tcReturnsConstraintKind to emphasise that they use the 'tcView' view of types. * Move these functions, and some related ones (tcIsLiftedTypeKind), from Kind.hs, to group together in Type.hs, alongside isPredTy. It feels very unsatisfactory that these 'tcX' functions live in Type, but it happens because isPredTy is called later in the compiler too. But it's a consequence of the 'Constraint vs Type' dilemma.
-
Simon Peyton Jones authored
Consider import M( C( a,b,c ) ) where class C is defined as module M where class C x where a :: blah c :: blah Tnen (Trac #15413) we'd like to get an error message only about failing to import C( b ), not C( a,b,c ). This was fairly easy (and local) to do. Turned out that the existing tests mod81 and mod91 are adequate tests for the feature.
-
Simon Peyton Jones authored
The reason for this change is described in TcUnify Note [Settting the argument context], and Trac #15438. The only effect is on error messages, where it stops GHC reporting an outright falsity (about the type signature for a function) when it finds an errors in a higher-rank situation. The testsuite changes in this patch illustrate the problem.
-
Simon Peyton Jones authored
The "non-local error" problem in Trac #14185 was due to the interaction of constraints from different function definitions. This patch makes a start towards fixing it. It adds TcUnify.alwaysBuildImplication to unconditionally build an implication in some cases, to keep the constraints from different functions separate. See the new Note [When to build an implication] in TcUnify. But a lot of error messages change, so for now I have set alwaysBuildImplication = False Result: no operational change at all. I'll get back to it!
-
- Jul 24, 2018
-
-
Summary: When looking for valid hole fits, the constraints relevant to the hole may sometimes contain a HoleDest. Previously, these were not cloned, which could cause the filling of filled coercion hole being, which would cause an assert to fail. This is now fixed. Test Plan: Regression test included. Reviewers: simonpj, bgamari, goldfire Reviewed By: simonpj Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15370 Differential Revision: https://phabricator.haskell.org/D5004
-
Krzysztof Gogolewski authored
Summary: RelaxedPolyRec is not used anymore Test Plan: validate Reviewers: bgamari, alpmestan Reviewed By: alpmestan Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4983
-
Summary: It's rather unfortunate that derived code can produce inaccessible code warnings (as demonstrated in #8128, #8740, and #15398), since the programmer has no control over the generated code. This patch aims to suppress `-Winaccessible-code` in all derived code. It accomplishes this by doing the following: * Generalize the `ic_env :: TcLclEnv` field of `Implication` to be of type `Env TcGblEnc TcLclEnv` instead. This way, it also captures `DynFlags`, which record the flag state at the time the `Implication` was created. * When typechecking derived code, turn off `-Winaccessible-code`. This way, any insoluble given `Implication`s that are created when typechecking this derived code will remember that `-Winaccessible-code` was disabled. * During error reporting, consult the `DynFlags` of an `Implication` before making the decision to report an inaccessible code warning. Test Plan: make test TEST="T8128 T8740 T15398" Reviewers: simonpj, bgamari Reviewed By: simonpj Subscribers: monoidal, rwbarton, thomie, carter GHC Trac Issues: #8128, #8740, #15398 Differential Revision: https://phabricator.haskell.org/D4993
-
Simon Peyton Jones authored
I was failing to instantiate vigorously enough in Type.piResultTys and in the very similar function ToIface.toIfaceAppArgsX This caused Trac #15428. The fix is easy. See Note [Care with kind instantiation] in Type.hs
-
- Jul 23, 2018
-
-
Simon Peyton Jones authored
We had a constraint (a b ~R# Int), and were marking it as 'insoluble'. That's bad; it isn't. And it caused Trac #15431. Soultion is simple. I did a tiny refactor on can_eq_app, so that it is used only for nominal equalities.
-
Richard Eisenberg authored
This fixes #15346, and is a team effort between Ryan Scott and myself (mostly Ryan). We discovered two errors related to FC's "push" rules, one in the TPush rule (as implemented in pushCoTyArg) and one in KPush rule (it shows up in liftCoSubstVarBndr). The solution: do what the paper says, instead of whatever random thoughts popped into my head as I was actually implementing. Also fixes #15419, which is actually the same underlying problem. Test case: dependent/should_compile/T{15346,15419}.
-
- Jul 22, 2018
-
-
Krzysztof Gogolewski authored
-
Krzysztof Gogolewski authored
This breaks Harbormaster builds.
-
Krzysztof Gogolewski authored
Test Plan: validate Reviewers: RyanGlScott, bgamari Reviewed By: RyanGlScott Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15365 Differential Revision: https://phabricator.haskell.org/D4998
-
Krzysztof Gogolewski authored
Summary: In D4592, `AddWordC` is lowered as an unsigned subtraction instead of an unsigned addition when compiling with LLVM. This patch rectifies that. Reviewers: angerman, bgamari, monoidal Reviewed By: angerman, bgamari, monoidal Subscribers: osa1, rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4969
-
Summary: `collectLStmtsBinders` was returning nothing for `ApplicativeStmts`, which caused the debugger to not track free variables in many cases when using `ApplicativeDo`. Test Plan: * new test case * validate Reviewers: bgamari, erikd Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15422 Differential Revision: https://phabricator.haskell.org/D4991
-
- Jul 21, 2018
-
-
David Feuer authored
Trac #15349 reveals that lazy blackholing can cause trouble for `fixST` much like it can for `fixIO`. Make `fixST` work just like `fixIO`. Reviewers: simonmar, hvr, bgamari Reviewed By: simonmar Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15349 Differential Revision: https://phabricator.haskell.org/D4948
-
Summary: This fixes the problem revealed by a new assert as it relates to valid hole fits. However, tests `T10384`, `T14040a` and `TcStaticPointersFail02` still fail the assert, but they are unrelated to valid hole fits. Reviewers: bgamari, simonpj Reviewed By: simonpj Subscribers: simonpj, rwbarton, thomie, carter GHC Trac Issues: #15384 Differential Revision: https://phabricator.haskell.org/D4994
-
- Jul 20, 2018
-
-
Summary: While working on [D904](https://phabricator.haskell.org/D4904), I noticed that 'findTopDir' was being invoked three times. This isn't a big problem, because it is usually very cheap. On windows, it does require some involved logic, though, so to me it would make sense to only run it once. Reviewers: bgamari, monoidal Reviewed By: monoidal Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4987
-
Summary: Previously, we were using `pprStmtContext` instead, which led to error messages missing indefinite articles where they were required. Test Plan: make test TEST="T13242a T7786 Typeable1" Reviewers: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15423 Differential Revision: https://phabricator.haskell.org/D4992
-
- Jul 19, 2018
-
-
Reviewers: bgamari, osa1 Reviewed By: osa1 Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4985
-
- Jul 18, 2018
-
-
Sergei Trofimovich authored
Before the change osReserveHeapMemory() attempted to allocate chunks of memory via osTryReserveHeapMemory() not multiple of MBLOCK_SIZE in the following fallback code: ``` if (at == NULL) { *len -= *len / 8; ``` and caused assertion failure: ``` $ make fulltest TEST=T11607 WAY=threaded1 T11607: internal error: ASSERTION FAILED: file rts/posix/OSMem.c, line 457 (GHC version 8.7.20180716 for riscv64_unknown_linux) ``` The change applies alignment mask before each MBLOCK allocation attempt and fixes WAY=threaded1 test failures on qemu-riscv64. Signed-off-by:
Sergei Trofimovich <slyfox@gentoo.org> Test Plan: run 'make fulltest WAY=threaded1' Reviewers: simonmar, bgamari, erikd Reviewed By: simonmar Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4982
-
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
-
- Jul 17, 2018
-
-
Reviewers: bgamari, osa1 Reviewed By: osa1 Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15410 Differential Revision: https://phabricator.haskell.org/D4979
-
Reviewers: bgamari, osa1 Reviewed By: osa1 Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15408 Differential Revision: https://phabricator.haskell.org/D4978
-
Reviewers: goldfire, bgamari, osa1 Reviewed By: osa1 Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15407 Differential Revision: https://phabricator.haskell.org/D4977
-
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>
-
Reviewers: goldfire, bgamari, mpickering Reviewed By: mpickering Subscribers: mpickering, goldfire, rwbarton, thomie, carter GHC Trac Issues: #15405 Differential Revision: https://phabricator.haskell.org/D4975
-
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
-