- 21 Jan, 2016 5 commits
-
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
When splitting H98/GADT syntax in ConDecl we lost a key kind-generalisation step. I also renamed tcHsTyVarBndrs to tcExplicitTKBnders, by analogy with tcImplicitTkBndrs. This fixes Trac #11459. Merge to 8.0.
-
Simon Peyton Jones authored
Re Trac #11051
-
Simon Peyton Jones authored
See Note [Free variables of types]. Richard to check.
-
Ben Gamari authored
-
- 20 Jan, 2016 7 commits
-
-
niteria authored
This fixes the immediate problem from https://s3.amazonaws.com/archive.travis-ci.org/jobs/103319396/log.txt Test Plan: ./validate Reviewers: bgamari, austin, thomie Differential Revision: https://phabricator.haskell.org/D1802 GHC Trac Issues: #11371
-
Thomas Miedema authored
Skip random tests when random is not built. Skip stm tests when stm is not built.
-
Add test for #9407. The test is only run on Windows 64bit, as this is where the problem occurred. Reviewed by: thomie Differential Revision: https://phabricator.haskell.org/D1806
-
Previously types defined by `GHC.Types` and `GHC.Prim` had their `Typeable` representations manually defined in `GHC.Typeable.Internals`. This was terrible, resulting in a great deal of boilerplate and a number of bugs due to missing or inconsistent representations (see #11120). Here we take a different tack, initially proposed by Richard Eisenberg: We wire-in the `Module`, `TrName`, and `TyCon` types, allowing them to be used in `GHC.Types`. We then allow the usual type representation generation logic to handle this module. `GHC.Prim`, on the other hand, is a bit tricky as it has no object code of its own. To handle this we instead place the type representations for the types defined here in `GHC.Types`. On the whole this eliminates several special-cases as well as a fair amount of boilerplate from hand-written representations. Moreover, we get full coverage of primitive types for free. Test Plan: Validate Reviewers: goldfire, simonpj, austin, hvr Subscribers: goldfire, simonpj, thomie Differential Revision: https://phabricator.haskell.org/D1774 GHC Trac Issues: #11120
-
We were previously using `if` in the derivation of `Ix` instances. This interacts badly with RebindableSyntax as the typechecker doesn't infer the type of the argument we give to `tagToEnum#`. Previously we produced, `if (ch >= ah) then (ch <= bh) else False`. We now produce `(ch >= ah) && (ch <= bh)` Fixes #11396. Test Plan: Validate Reviewers: austin, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1797 GHC Trac Issues: #11396
-
Simon Peyton Jones authored
This fixes 514bac26 for Trac #11172. Sorry!
-
Simon Peyton Jones authored
This long-standing bug in CoreUtils.combineIdenticalAlts was shown up by Trac #11172. The effect was that it returned a correct set of alternatives, but a bogus set of "impossible default constructors". That meant that we subsequently removed all the alternatives from a case, and hence ended up with a bogusly empty case that should not have been empty. See Note [Care with impossible-constructors when combining alternatives] in CoreUtils.
-
- 19 Jan, 2016 5 commits
-
-
Ömer Sinan Ağacan authored
-
Ömer Sinan Ağacan authored
- This is only used for printing purposes (in :browse etc.). - Fixes #11266. Reviewers: goldfire, bgamari, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1799 GHC Trac Issues: #11266
-
Simon Marlow authored
For backwards-compat with GHC 7.10.
-
niteria authored
This adds sanity checks to `substTy` that implement: > when calling substTy subst ty it should be the case that the in-scope > set in the substitution is a superset of > * The free vars of the range of the substitution > * The free vars of ty minus the domain of the substitution and replaces violators with unchecked version. The violators were found by running the GHC test suite. This ensures that I can work on this incrementally and that what I fix won't be undone by some other change. It also includes a couple of fixes that I've already done. Test Plan: ./validate Reviewers: simonmar, goldfire, simonpj, austin, bgamari Reviewed By: simonpj, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1792 GHC Trac Issues: #11371
-
Gabor Greif authored
-
- 18 Jan, 2016 18 commits
-
-
Reviewers: austin Subscribers: thomie, ezyang Differential Revision: https://phabricator.haskell.org/D1793 GHC Trac Issues: #11448
-
Reviewers: austin Reviewed By: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1796
-
This hides derived OccNames from the Names returned from runDeclsWithLocation and clarifies the documentation. This is done to ensure that these names (originating from, e.g., derived Generic instances and type representation bindings) don't show up in ghci output when run with `:set +t`. This fixes #11051. Test Plan: Validate with included tests Reviewers: austin Reviewed By: austin Subscribers: thomie, hvr Differential Revision: https://phabricator.haskell.org/D1794 GHC Trac Issues: #11051
-
Test Plan: Validate Reviewers: simonmar, thomie, austin Reviewed By: austin Subscribers: alanz Differential Revision: https://phabricator.haskell.org/D1789
-
A small cosmetic change, but we have to do a bit of work to actually support it: - Cabal submodule update, so that Cabal passes us -this-unit-id when we ask for it. This includes a Cabal renaming to be consistent with Unit ID, which makes ghc-pkg a bit more scrutable. - Build system is updated to use -this-unit-id rather than -this-package-key, to avoid deprecation warnings. Needs a version test so I resurrected the old test we had (sorry rwbarton!) - I've *undeprecated* -package-name, so that we are in the same state as GHC 7.10, since the "correct" flag will have only entered circulation in GHC 8.0. - I removed -package-key. Since we didn't deprecate -package-id I think this should not cause any problems for users; they can just change their code to use -package-id. - The package database is indexed by UNIT IDs, not component IDs. I updated the naming here. - I dropped the signatures field from ExposedModule; nothing was using it, and instantiatedWith from the package database field. - ghc-pkg was updated to use unit ID nomenclature, I removed the -package-key flags but I decided not to add any new flags for now. Signed-off-by:
Edward Z. Yang <ezyang@cs.stanford.edu> Test Plan: validate Reviewers: austin, hvr, bgamari Reviewed By: bgamari Subscribers: 23Skidoo, thomie, erikd Differential Revision: https://phabricator.haskell.org/D1780
-
Jan Stolarek authored
Summary: In the past the canonical way for constructing an SDoc string literal was the composition `ptext . sLit`. But for some time now we have function `text` that does the same. Plus it has some rules that optimize its runtime behaviour. This patch takes all uses of `ptext . sLit` in the compiler and replaces them with calls to `text`. The main benefits of this patch are clener (shorter) code and less dependencies between module, because many modules now do not need to import `FastString`. I don't expect any performance benefits - we mostly use SDocs to report errors and it seems there is little to be gained here. Test Plan: ./validate Reviewers: bgamari, austin, goldfire, hvr, alanz Subscribers: goldfire, thomie, mpickering Differential Revision: https://phabricator.haskell.org/D1784
-
Simon Marlow authored
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
This fixes Trac #11351. The implementation is pretty simple, happily. I took the opportunity to re-order the prov/req context in builder-ids, which was confusingly backwards.
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
Some modest refactoring, triggered in part by Trac #11051 * Kill off PatSynId, ReflectionId in IdDetails They were barely used, and only for pretty-printing * Add helper function Id.mkExportedVanillaId, and use it * Polish up OccName.isDerivedOccName, as a predicate for definitions generated internally by GHC, which we might not want to show to the user. * Kill off unused OccName.mkDerivedTyConOcc * Shorten the derived OccNames for newtype and data instance axioms * A bit of related refactoring around newFamInstAxiomName
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
This bug was thrown up by Trac #11361, but I found that the problem was deeper: GHC was allowing class C a where type F (a :: k) :: * type F (x :: *) = x -- Not right! (Which is now indexed-types/should_compile/T11361a.) Anyway the fix is relatively simple; use tcMatchTys in tcDefaultAssocDecl. Merge to 8.0 branch.
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
Previously tcMatchTys took a set of "template type variables" to bind. But all the calls are top-level, and we always want to bind all variables in the template. So I simplified the API by omitting that argument. There should be no change in behaviour. Feel free to merge to 8.0 if it helps in merging other patches
-
I missed a crucial step in the wiring-in process of `CallStack` in D861, the bit where you actually wire-in the Name... This led to a nasty bug where GHC thought `CallStack` was not wired-in and tried to fingerprint it, which failed because the defining module was not loaded. But we don't need `CallStack` to be wired-in anymore since `error` and `undefined` no longer need to be wired-in. So we just remove them all. Updates haddock submodule. Test Plan: `./validate` and `make slowtest TEST=tc198` Reviewers: simonpj, goldfire, austin, hvr, bgamari Reviewed By: simonpj, bgamari Subscribers: goldfire, thomie Projects: #ghc Differential Revision: https://phabricator.haskell.org/D1739 GHC Trac Issues: #11331
-
- 17 Jan, 2016 5 commits
-
-
Test Plan: validate, check that gz is used Reviewers: hvr, austin, thomie Reviewed By: thomie Differential Revision: https://phabricator.haskell.org/D1788 GHC Trac Issues: #11434
-
Reviewers: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1790 GHC Trac Issues: #11414
-
Kind equalities changed how `*`/`#` are represented internally, which means that showing a `TypeRep` that contains either of those kinds produces a rather gross-looking result, e.g., ``` > typeOf (Proxy :: Proxy 'Just) Proxy (TYPE 'Lifted -> Maybe (TYPE 'Lifted)) 'Just ``` We can at least special-case the `Show` instance for `TypeRep` so that it prints `*` to represent `TYPE 'Lifted` and `#` to represent `TYPE 'Unlifted`. Addresses one of the issues uncovered in #11334. Test Plan: ./validate Reviewers: simonpj, hvr, austin, goldfire, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1757 GHC Trac Issues: #11334
-
Fix operator completions: list of suitable completions only rather than everything from imported modules. Signed-off-by:
Arthur Fayzrakhmanov (Артур Файзрахманов) <heraldhoi@gmail.com> ghc: fix operator completions Reviewers: austin, hvr, thomie, bgamari Reviewed By: thomie, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1058 GHC Trac Issues: #10576
-
Test Plan: Build then clean Reviewers: austin, thomie Reviewed By: thomie Differential Revision: https://phabricator.haskell.org/D1786 GHC Trac Issues: #11433
-