- Jan 18, 2018
-
-
Ryan Scott authored
It turns out that `Convert` was recklessly leaving off parentheses in two places: * Negative numeric literals * Patterns in lambda position This patch fixes it by adding three new functions, `isCompoundHsLit`, `isCompoundHsOverLit`, and `isCompoundPat`, and using them in the right places in `Convert`. While I was in town, I also sprinkled `isCompoundPat` among some `Pat`-constructing functions in `HsUtils` to help avoid the likelihood of this problem happening in other places. One of these places is in `TcGenDeriv`, and sprinkling `isCompountPat` there fixes #14682 Test Plan: make test TEST="T14681 T14682" Reviewers: alanz, goldfire, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14681, #14682 Differential Revision: https://phabricator.haskell.org/D4323 (cherry picked from commit 575c009d)
-
Andreas Klebinger authored
On Windows GHC enforces currently that the real executable is named ghc.exe/ghc-stage[123].exe. I don't see a good reason why this is neccessary. This patch removes this restriction and fixes #14652 Test Plan: ci Reviewers: bgamari, Phyx Reviewed By: Phyx Subscribers: Phyx, rwbarton, thomie, carter GHC Trac Issues: #14652 Differential Revision: https://phabricator.haskell.org/D4296 (cherry picked from commit 1bf70b20)
-
Tao He authored
Reviewers: bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14653 Differential Revision: https://phabricator.haskell.org/D4305 (cherry picked from commit 2feed118)
-
This implements SPJ's suggestion on the ticket (#14273). We find the relevant constraints (ones that whose free unification variables are all mentioned in the type of the hole), and then clone the free unification variables of the hole and the relevant constraints. We then add a subsumption constraints and run the simplifier, and then check whether all the constraints were solved. Reviewers: bgamari Reviewed By: bgamari Subscribers: RyanGlScott, rwbarton, thomie, carter GHC Trac Issues: #14273 Differential Revision: https://phabricator.haskell.org/D4315 (cherry picked from commit 1e14fd3e)
-
Ryan Scott authored
Previously, GHC was pretty-printing left-section holes incorrectly and not parsing right-sectioned holes at all. This patch fixes both problems. Test Plan: make test TEST=T14590 Reviewers: bgamari, simonpj Reviewed By: simonpj Subscribers: simonpj, rwbarton, thomie, mpickering, carter GHC Trac Issues: #14590 Differential Revision: https://phabricator.haskell.org/D4273 (cherry picked from commit 4d41e921)
-
- Jan 17, 2018
-
-
Test Plan: validate Reviewers: bgamari, niteria, erikd, dfeuer Reviewed By: dfeuer Subscribers: Yuras, dfeuer, rwbarton, thomie, carter GHC Trac Issues: #14497 Differential Revision: https://phabricator.haskell.org/D4254 (cherry picked from commit fb1f0a46)
-
- Jan 15, 2018
-
-
Substitute RanlibCmd for consistency, and other configure cleanups that should have no effect The other commands are so substituted. Maybe we don't need ranlib at all, and the configure snippet can be removed all together, but that can always be done later. Reviewers: bgamari, hvr, angerman Reviewed By: bgamari, angerman Subscribers: rwbarton, thomie, erikd, carter Differential Revision: https://phabricator.haskell.org/D4286 (cherry picked from commit 8de89305)
-
Ryan Scott authored
Trac #14646 happened because we forgot to parenthesize `forall` types to the left of an arrow. This simple patch fixes that. Test Plan: make test TEST=T14646 Reviewers: alanz, goldfire, bgamari Reviewed By: alanz Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14646 Differential Revision: https://phabricator.haskell.org/D4298 (cherry picked from commit f380115c)
-
Simon Peyton Jones authored
This patch moves the "ok_unfolding" test from CoreOpt.joinPointBinding_maybe to OccurAnal.decideJoinPointHood Previously the occurrence analyser was deciding to make something a join point, but the simplifier was reversing that decision, which made the decision about /other/ bindings invalid. Fixes Trac #14650. (cherry picked from commit 66ff794f)
-
- Jan 14, 2018
-
-
Simon Peyton Jones authored
This is a pure refactoring. Use HsConDetails to implement HsPatSynDetails, instead of defining a whole new data type. Less code, fewer types, all good. (cherry picked from commit 584cbd4a)
-
Simon Peyton Jones authored
This recent patch commit 1577908f Author: Simon Peyton Jones <simonpj@microsoft.com> Date: Tue Jan 9 16:20:46 2018 +0000 Fix two more bugs in partial signatures These were shown up by Trac #14643 failed validation for typecheck/should_run/T10846 (Reported in Trac #14658.) The fix is simple. (cherry picked from commit f3f90a07)
-
Simon Peyton Jones authored
These were shown up by Trac #14643 Bug 1: if we had a single partial signature for two functions f, g :: forall a. _ -> a then we made two different SigTvs but with the sane Name. This was jolly confusing and ultimately led to deeply bogus results with Any's appearing in the resulting program. Yikes. Fix: clone the quantified variables in TcSigs.tcInstSig (as indeed its name suggests). Bug 2: we were not eliminating duplicate/superclass constraints in the partial signatures of a mutually recursive group. Easy to fix: we are already doing dup/superclass elim in TcSimplify.decideQuantification. So we move the partial-sig constraints there too. (cherry picked from commit 1577908f)
-
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)
-