- Jan 14, 2018
-
-
Ryan Scott authored
This adds a regression test for the original program in #14040. This does not fix #14040 entirely, though, as the program in https://ghc.haskell.org/trac/ghc/ticket/14040#comment:2 still panics, so there is more work to be done there. (cherry picked from commit be1ca0e4)
-
Simon Peyton Jones authored
Trac #13032 pointed out that we sometimes generate unused bindings for Givens, and (worse still) we can't always discard them later (we don't drop a case binding unless we can prove that the scrutinee is non-bottom. It looks as if this may be a major reason for the performace problems in #14338 (see comment:29). This patch fixes the problem at source, by pruning away all the dead Givens. See Note [Delete dead Given evidence bindings] Remarkably, compiler allocation falls by 23% in perf/compiler/T12227! I have not confirmed whether this change actualy helps with (cherry picked from commit 954cbc7c)
-
Simon Peyton Jones authored
This rather subtle patch fixes Trac #14584. The problem was that we'd allowed a coercion, bound in a nested scope, to escape into an outer scope. The main changes are * TcSimplify.floatEqualities takes more care when floating equalities to make sure we don't float one out that mentions a locally-bound coercion. See Note [What prevents a constraint from floating] * TcSimplify.emitResidualConstraints (which emits the residual constraints in simplifyInfer) now avoids burying the constraints for escaping CoVars inside the implication constraint. * Since I had do to this stuff with CoVars, I moved the fancy footwork about not quantifying over CoVars from TcMType.quantifyTyVars to its caller TcSimplify.decideQuantifiedTyVars. I think its other callers don't need to worry about all this CoVar stuff. This turned out to be surprisigly tricky, and took me a solid day to get right. I think the result is reasonably neat, though, and well documented with Notes. (cherry picked from commit f5cf9d1a)
-
Simon Peyton Jones authored
In fixing Trac #14584 I found that it would be /much/ more convenient if a "hole" in a coercion (much like a unification variable in a type) acutally had a CoVar associated with it rather than just a Unique. Then I can ask what the free variables of a coercion is, and get a set of CoVars including those as-yet-un-filled in holes. Once that is done, it makes no sense to stuff coercion holes inside UnivCo. They were there before so we could know the kind and role of a "hole" coercion, but once there is a CoVar we can get that info from the CoVar. So I removed HoleProv from UnivCoProvenance and added HoleCo to Coercion. In summary: * Add HoleCo to Coercion and remove HoleProv from UnivCoProvanance * Similarly in IfaceCoercion * Make CoercionHole have a CoVar in it, not a Unique * Make tyCoVarsOfCo return the free coercion-hole variables as well as the ordinary free CoVars. Similarly, remember to zonk the CoVar in a CoercionHole We could go further, and remove CoercionHole as a distinct type altogther, just collapsing it into HoleCo. But I have not done that yet. (cherry picked from commit a492af06)
-
Simon Peyton Jones authored
This fixes Trac #14479. Not difficult. See Note [Quantification and partial signatures] Wrinkle 4, in TcSimplify. (cherry picked from commit 72938f58)
-
Simon Peyton Jones authored
This patch fixes two bugs in the treatment of SigTvs at the kind level: - We should always generalise them, never default them (Trac #14555, #14563) - We should check if they get unified with each other (Trac #11203) Both are described in TcHsType Note [Kind generalisation and SigTvs] (cherry picked from commit 8361b2c5)
-
Simon Peyton Jones authored
This refactoring * Renames kcHsTyVarBndrs to kcLHsQTyVars, which is more truthful. It is only used in getInitialKind. * Pulls out bind_telescope from that function, and calls it kcLHsTyVarBndrs, again to reflect its argument * Uses the new kcLHsTyVarBndrs in kcConDecl, where the old function was wild overkill. There should not be any change in behaviour (cherry picked from commit de204409)
-
- Jan 12, 2018
-
-
when read notifications are requested, too (#13903) Signed-off-by:
Matthias Treydte <mt@waldheinz.de> KQueue: Drop Bits/FiniteBits instances for Filter as they are really constants whose bits should not be fiddled with Signed-off-by:
Matthias Treydte <mt@waldheinz.de> Reviewers: austin, hvr, bgamari Reviewed By: bgamari Subscribers: gridaphobe, kazu_yamamoto, rwbarton, thomie GHC Trac Issues: #13903 Differential Revision: https://phabricator.haskell.org/D3692 (cherry picked from commit 6c3eafb3)
-
Ryan Scott authored
Summary: `GeneralizedNewtypeDeriving` generates calls to `coerce` which take visible type arguments. These types must be produced by way of `typeToLHsType`, which converts a `Type` to an `LHsType`. However, `typeToLHsType` was leaving off important kind information when a `Type` contained a poly-kinded tycon application, leading to incorrectly generated code in #14579. This fixes the issue by tweaking `typeToLHsType` to generate explicit kind signatures for tycon applications. This makes the generated code noisier, but at least the program from #14579 now works correctly. Test Plan: make test TEST=T14579 Reviewers: simonpj, bgamari Reviewed By: simonpj Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14579 Differential Revision: https://phabricator.haskell.org/D4264 (cherry picked from commit 649e7772)
-
Ryan Scott authored
Summary: The `HsType` pretty-printer does not automatically insert parentheses where necessary for type applications, so a function `isCompoundHsType` was created in D4056 towards this purpose. However, it was not used in as many places as it ought to be, resulting in #14578. Test Plan: make test TEST=T14578 Reviewers: alanz, bgamari, simonpj Reviewed By: alanz, simonpj Subscribers: simonpj, rwbarton, thomie, carter GHC Trac Issues: #14578 Differential Revision: https://phabricator.haskell.org/D4266 (cherry picked from commit 1bd91a7a)
-
Christiaan Baaij authored
Summary: To be in line with the other typeNatTyCons Reviewers: bgamari, RyanGlScott Reviewed By: RyanGlScott Subscribers: RyanGlScott, rwbarton, thomie, carter GHC Trac Issues: #14632 Differential Revision: https://phabricator.haskell.org/D4284 (cherry picked from commit fb78b0d2)
-
- Jan 08, 2018
-
-
Ryan Scott authored
Commit fa8035e3 added `Div` and `Mod` type families to `GHC.TypeNats`. However, they did not add the corresponding fixities! Currently, we have that both `div` and `mod` (at the value level) are `infixl 7`, so we should adopt the same fixities for the type-level `Div` and `Mod` as well. Test Plan: It compiles Reviewers: hvr, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14640 Differential Revision: https://phabricator.haskell.org/D4291 (cherry picked from commit 303106d5)
-
- Jan 04, 2018
-
-
Ryan Scott authored
Commit 714bebff removed a check in the bytecode compiler that caught illegal uses of unboxed tuples (and now sums) in case alternatives, which causes the program in #14608 to panic. This restores the check (using modern, levity-polymorphic vocabulary). Test Plan: make test TEST=T14608 Reviewers: hvr, bgamari, dfeuer, simonpj Reviewed By: dfeuer, simonpj Subscribers: simonpj, rwbarton, thomie, carter GHC Trac Issues: #14608 Differential Revision: https://phabricator.haskell.org/D4276 (cherry picked from commit ecff651f)
-
This calls out to the Win32 API `GetTempFileName` to generate a temporary file. Using `uUnique = 0` guarantees that the file we get back is unique and the file is "reserved" by creating it. Test Plan: ./validate I can't think of any sensible tests that shouldn't run for a while to verify. So the example in #10731 was ran for a while and no collisions in new code Reviewers: hvr, bgamari, erikd Reviewed By: bgamari Subscribers: RyanGlScott, rwbarton, thomie, carter GHC Trac Issues: #10731 Differential Revision: https://phabricator.haskell.org/D4278 (cherry picked from commit 46287af0)
-
- Dec 28, 2017
-
-
Previously, we were inexplicably not applying an instantiating substitution to arguments in non-prenex types. It's amazing this has been around for so long! I guess there aren't a lot of non-prenex types around. test case: typecheck/should_fail/T14618 (cherry picked from commit 722a6584)
-
- Dec 22, 2017
-
-
Ben Gamari authored
(cherry picked from commit e237e1f1)
-
Ben Gamari authored
Split-sections unfortunately isn't yet working.
-
Ben Gamari authored
-
Ben Gamari authored
Prior to 8.0.2 MultiWayIf syntax required that the -> token be indented relative to the guard. See #10807.
-
- Dec 21, 2017
-
-
Herbert Valerio Riedel authored
[skip ci] (cherry picked from commit 4d99a665)
-
- Dec 20, 2017
-
-
Herbert Valerio Riedel authored
[skip ci] (cherry picked from commit 00565677)
-
- Dec 14, 2017
-
-
Ben Gamari authored
-
Ben Gamari authored
-
Ben Gamari authored
-
We filter the complete patterns given in a COMPLETE set to only those that subsume the type we are matching. Otherwise we end up introducing an ill-typed equation into the overlap checking, provoking a crash. This was the cause of Trac #14135. Reviewers: austin, bgamari, mpickering, gkaracha, simonpj, RyanGlScott, carlostome Reviewed By: bgamari Subscribers: carter, dfeuer, RyanGlScott, goldfire, rwbarton, thomie GHC Trac Issues: #14135 Differential Revision: https://phabricator.haskell.org/D3981 (cherry picked from commit 16c7d9dc)
-
This fixes Issue #12372: documentation for Control.Monad.guard not useful after AMP. Reviewers: hvr, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4258 (cherry picked from commit 6847c6bf)
-
Gabor Greif authored
Because in recent RHEL7 suddenly locales like `bokmål` pop up, which screw up reading-in of ASCII strings a line later. This additional criterion reliably eliminates those unicode characters. (cherry picked from commit abd5db60)
-
- Dec 11, 2017
-
-
David Feuer authored
* Add a new flag, `-fignore-optim-changes`, allowing them to avoid recompilation if the only changes are to the `-O` level or to flags controlling optimizations. * When `-fignore-optim-changes` is *off*, recompile when optimization flags (e.g., `-fno-full-laziness`) change. Previously, we ignored these unconditionally when deciding whether to recompile a module. Reviewers: austin, bgamari, simonmar Reviewed By: simonmar Subscribers: duog, carter, simonmar, rwbarton, thomie GHC Trac Issues: #13604 Differential Revision: https://phabricator.haskell.org/D4123 (cherry picked from commit 708ed9ca)
-
This was presumably a vestige of the days when the profiled RTS couldn't run threaded. Fixes #14545. Test Plan: simonmar Reviewers: erikd, simonmar Reviewed By: simonmar Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14545 Differential Revision: https://phabricator.haskell.org/D4245 (cherry picked from commit 4bfff7a5)
-
open() can sometimes take a long time, for example on NFS or FUSE filesystems. We recently had a case where open() was taking multiple seconds to return for a (presumably overloaded) FUSE filesystem, which blocked GC and caused severe issues. Test Plan: validate Reviewers: niteria, bgamari, nh2, hvr, erikd Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #13296 Differential Revision: https://phabricator.haskell.org/D4239 (cherry picked from commit cafe9834)
-
Ben Gamari authored
It will remain a submodule until we are ready to merge Hadrian into the tree.
-
Ben Gamari authored
Sadly subtrees haven't worked quite as well as we would have liked for developers. See Hadrian #440.
-
Ben Gamari authored
Updates haddock dsubmodule
-
- Dec 04, 2017
-
-
Ben Gamari authored
The LaTeX produced by this previously failed to compile. Changing the first cell of the row from an inline to a paragraph fixes this. Then I noticed that the table overflowed the page. This is fixed by applying the longtable class.
-
Ben Gamari authored
This was scheduled to happen for 8.2, it looks like it will actually happen in 8.4.
-
David Feuer authored
Matching with the `Con` and `Con'` patterns can reveal evidence that the type in question is *not* an application. This can help the pattern checker. Reviewers: austin, hvr, bgamari Reviewed By: bgamari Subscribers: carter, rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D4139
-
- Dec 01, 2017
-
-
David Feuer authored
Cache `TypeRep k` in each `TrApp` or `TrTyCon` constructor of `TypeRep (a :: k)`. This makes `typeRepKind` cheap. With this change, we won't need any special effort to deserialize typereps efficiently. The downside, of course, is that we make `TypeRep`s slightly larger. Reviewers: austin, hvr, bgamari, simonpj Reviewed By: bgamari, simonpj Subscribers: carter, simonpj, rwbarton, thomie GHC Trac Issues: #14254 Differential Revision: https://phabricator.haskell.org/D4085
-
David Feuer authored
Add support for injecting runtime calls to `trace` in `DsM`. This allows the desugarer to add compile-time information to a runtime trace. Reviewers: austin, hvr, bgamari Reviewed By: bgamari Subscribers: carter, thomie, rwbarton Differential Revision: https://phabricator.haskell.org/D4162
-
Edward Z. Yang authored
Summary: Previously, we attempted to lookup 'hole' packages for include directories; this obviously is not going to work. Signed-off-by:
Edward Z. Yang <ezyang@fb.com> Test Plan: validate Reviewers: ekmett, bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #14525 Differential Revision: https://phabricator.haskell.org/D4234
-
Edward Z. Yang authored
Summary: Suppose that you are typechecking A.hs, which transitively imports, via B.hs, A.hs-boot. When we poke on B.hs and discover that it has a reference to a type from A, what TyThing should we wire it up with? Clearly, if we have already typechecked A, we should use the most up-to-date TyThing: the one we freshly generated when we typechecked A. But what if we haven't typechecked it yet? For the longest time, GHC adopted the policy that this was *an error condition*; that you MUST NEVER poke on B.hs's reference to a thing defined in A.hs until A.hs has gotten around to checking this. However, actually ensuring this is the case has proven to be a bug farm. The problem was especially poignant with type family consistency checks, which eagerly happen before any typechecking takes place. This patch takes a different strategy: if we ever try to access an entity from A which doesn't exist, we just fall back on the definition of A from the hs-boot file. This means that you may end up with a mix of A.hs and A.hs-boot TyThings during the course of typechecking. Signed-off-by:
Edward Z. Yang <ezyang@fb.com> Test Plan: validate Reviewers: simonpj, bgamari, austin, goldfire Subscribers: thomie, rwbarton GHC Trac Issues: #14396 Differential Revision: https://phabricator.haskell.org/D4154
-