- 18 Jan, 2016 13 commits
-
-
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
-
Eric Seidel authored
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 6 commits
-
-
Ben Gamari authored
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
-
Ben Gamari authored
Reviewers: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1790 GHC Trac Issues: #11414
-
Ryan Scott authored
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
-
Geraldus authored
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
-
Ben Gamari authored
Test Plan: Build then clean Reviewers: austin, thomie Reviewed By: thomie Differential Revision: https://phabricator.haskell.org/D1786 GHC Trac Issues: #11433
-
Ben Gamari authored
Test Plan: Validate Reviewers: simonmar, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1787 GHC Trac Issues: #11300
-
- 16 Jan, 2016 4 commits
-
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
As a result of some other unrelated changes I found that IndTypesPerf was failing, and opened Trac #11408. There's a test in indexed-types/should-compile/T11408. The bug was that a type like forall t. (MT (UL t) (UR t) ~ t) => UL t -> UR t -> Int is in fact unambiguous, but it's a bit subtle to prove that it is unambiguous. In investigating, Dimitrios and I found several subtle bugs in the constraint solver, fixed by this patch * canRewrite was missing a Derived/Derived case. This was lost by accident in Richard's big kind-equality patch. * Interact.interactTyVarEq would discard [D] a ~ ty if there was a [W] a ~ ty in the inert set. But that is wrong because the former can rewrite things that the latter cannot. Fix: a new function eqCanDischarge * In TcSMonad.addInertEq, the process was outright wrong for a Given/Wanted in the (GWModel) case. We were adding a new Derived without kicking out things that it could rewrite. Now the code is simpler (no special GWModel case), and works correctly. * The special case in kickOutRewritable for [W] fsk ~ ty, turns out not to be needed. (We emit a [D] fsk ~ ty which will do the job. I improved comments and documentation, esp in TcSMonad.
-
Alan Zimmerman authored
Summary: Certain syntactic elements have integers in them, such as fixity specifications, SPECIALISE pragmas and so on. The lexer will accept mult-radix literals, with arbitrary leading zeros in these. Bring in a SourceText field to each affected AST element to capture the original literal text for use with API Annotations. Affected hsSyn elements are ``` -- See note [Pragma source text] data Activation = NeverActive | AlwaysActive | ActiveBefore SourceText PhaseNum -- Active only *strictly before* this phase | ActiveAfter SourceText PhaseNum -- Active in this phase and later deriving( Eq, Data, Typeable ) -- Eq used in comparing rules in HsDecls data Fixity = Fixity SourceText Int FixityDirection -- Note [Pragma source text] deriving (Data, Typeable) ``` and ``` | HsTickPragma -- A pragma introduced tick SourceText -- Note [Pragma source text] in BasicTypes (StringLiteral,(Int,Int),(Int,Int)) -- external span for this tick ((SourceText,SourceText),(SourceText,SourceText)) -- Source text for the four integers used in the span. -- See note [Pragma source text] in BasicTypes (LHsExpr id) ``` Updates haddock submodule Test Plan: ./validate Reviewers: goldfire, bgamari, austin Reviewed By: bgamari Subscribers: thomie, mpickering Differential Revision: https://phabricator.haskell.org/D1781 GHC Trac Issues: #11430
-
Rik Steenkamp authored
Differential Revision: https://phabricator.haskell.org/D1785
-
- 15 Jan, 2016 17 commits
-
-
eir@cis.upenn.edu authored
This adds a new variant of AbsBinds that is used solely for bindings with a type signature. This allows for a simpler desugaring that does not produce the bogus output that tripped up Core Lint in ticket #11405. Should make other desugarings simpler, too.
-
eir@cis.upenn.edu authored
-
eir@cis.upenn.edu authored
-
eir@cis.upenn.edu authored
We now check for unused variables one at a time, instead of all at the top. Test: dependent/should_compile/T11405
-
eir@cis.upenn.edu authored
This addresses #11405, but a deeper problem lurks. Try test dependent/should_compile/T11405 and see comment:3 on the ticket.
-
eir@cis.upenn.edu authored
This moves the call to tcSubType into the context of the checkInstConstraints call, allowing the deferred type error somewhere to hang its hat.
-
eir@cis.upenn.edu authored
This is mentioned in #11376.
-
eir@cis.upenn.edu authored
All things of kind *, including * itself, need to have a PtrRep. Test: dependent/should_compile/T11311
-
eir@cis.upenn.edu authored
This moves the duplicate-unique check from knownKeyNames (which omits TH) to allKnownKeyNames (which includes TH).
-
eir@cis.upenn.edu authored
This one worked for me out of the box.
-
eir@cis.upenn.edu authored
Previously, the check for impredicative type applications was in the wrong spot. Test case: typecheck/should_fail/T11355
-
Ryan Scott authored
Before, it was possible to have a datatypes such as ``` type ConstantT a b = a newtype T (f :: * -> *) (a :: ConstantT * f) = T (f a) deriving Functor data family TFam (f :: * -> *) (a :: *) newtype instance TFam f (ConstantT a f) = TFam (f a) deriving Functor ``` fail to eta-reduce because either (1) a TyVar had a kind synonym that mentioned another TyVar, or (2) an instantiated type was itself a type synonym that mentioned another TyVar. A little bit of tweaking to `expandTypeSynonyms` and applying it before the eta-reduction check in the `deriving` machinery is sufficient to fix this. Fixes #11416. Test Plan: ./validate Reviewers: goldfire, simonpj, austin, bgamari Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1772 GHC Trac Issues: #11416
-
Matthew Pickering authored
But still disallow empty pattern synonym builder declarations. Handling this incorrectly was the cause of #11367. Test Plan: ./validate Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1779 GHC Trac Issues: #11367
-
kgardas authored
Reviewers: austin, bgamari, thomie Reviewed By: thomie Subscribers: angerman, thomie, erikd Differential Revision: https://phabricator.haskell.org/D1775
-
Ryan Scott authored
Test Plan: ./validate Reviewers: goldfire, austin, bgamari, simonpj Subscribers: simonpj, thomie Differential Revision: https://phabricator.haskell.org/D1766 GHC Trac Issues: #11345
-
Ben Gamari authored
Test Plan: Validate Reviewers: austin, thomie, nomeata Differential Revision: https://phabricator.haskell.org/D1782 GHC Trac Issues: #11433
-
Ben Gamari authored
Resolves #11434.
-