- Sep 11, 2016
-
-
Matthew Pickering authored
You can now just use `mkMatchGroup`.
-
- Sep 05, 2016
-
-
Facundo Domínguez authored
Summary: Module finalizer could call addTopDecls, however, the declarations added in this fashion were ignored. This patch makes sure to rename, type check and incorporate this declarations. Because a declaration may include a splice which calls addModFinalizer, the list of finalizers is repeteadly checked after adding declarations until no more finalizers remain. Test Plan: ./validate Reviewers: bgamari, goldfire, simonpj, austin Reviewed By: bgamari, simonpj Subscribers: simonmar, mboes, thomie Differential Revision: https://phabricator.haskell.org/D2505 GHC Trac Issues: #12559
-
- Aug 31, 2016
-
-
We need to compare against the local return and pure, not returnMName and pureAName. Fixes #12490. Test Plan: Validate, add testcase Reviewers: austin, simonmar Reviewed By: simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2499 GHC Trac Issues: #12490
-
- Aug 26, 2016
-
-
Simon Peyton Jones authored
This fixes Trac #12531: class Foo x where foo :: forall a . x a -> x a default foo :: forall b . x b -> x b foo x = go where go :: x b go = undefined We want 'b' to scope over the code for 'foo', but we were using 'a' instead.
-
- Aug 12, 2016
-
-
Simon Peyton Jones authored
Fixes Trac #12484
-
- Jul 26, 2016
-
-
Edward Z. Yang authored
Summary: Three things in this commit: 1. Get rid of sb_ids; we are not going to use them to avoid infinite unfoldings in hs-boot files. 2. Compute sb_tcs from ModIface rather than ModDetails. This means that the typechecker can look at this field without forcing the boot ModDetails, which would be bad if the ModDetails is not available yet (due to knot tying.) 3. A big honking comment explaining what is going on here. Signed-off-by:
Edward Z. Yang <ezyang@cs.stanford.edu> Reviewers: simonpj, austin, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2380
-
- Jul 21, 2016
-
-
Ömer Sinan Ağacan authored
Summary: This patch implements primitive unboxed sum types, as described in https://ghc.haskell.org/trac/ghc/wiki/UnpackedSumTypes. Main changes are: - Add new syntax for unboxed sums types, terms and patterns. Hidden behind `-XUnboxedSums`. - Add unlifted unboxed sum type constructors and data constructors, extend type and pattern checkers and desugarer. - Add new RuntimeRep for unboxed sums. - Extend unarise pass to translate unboxed sums to unboxed tuples right before code generation. - Add `StgRubbishArg` to `StgArg`, and a new type `CmmArg` for better code generation when sum values are involved. - Add user manual section for unboxed sums. Some other changes: - Generalize `UbxTupleRep` to `MultiRep` and `UbxTupAlt` to `MultiValAlt` to be able to use those with both sums and tuples. - Don't use `tyConPrimRep` in `isVoidTy`: `tyConPrimRep` is really wrong, given an `Any` `TyCon`, there's no way to tell what its kind is, but `kindPrimRep` and in turn `tyConPrimRep` returns `PtrRep`. - Fix some bugs on the way: #12375. Not included in this patch: - Update Haddock for new the new unboxed sum syntax. - `TemplateHaskell` support is left as future work. For reviewers: - Front-end code is mostly trivial and adapted from unboxed tuple code for type checking, pattern checking, renaming, desugaring etc. - Main translation routines are in `RepType` and `UnariseStg`. Documentation in `UnariseStg` should be enough for understanding what's going on. Credits: - Johan Tibell wrote the initial front-end and interface file extensions. - Simon Peyton Jones reviewed this patch many times, wrote some code, and helped with debugging. Reviewers: bgamari, alanz, goldfire, RyanGlScott, simonpj, austin, simonmar, hvr, erikd Reviewed By: simonpj Subscribers: Iceland_jack, ggreif, ezyang, RyanGlScott, goldfire, thomie, mpickering Differential Revision: https://phabricator.haskell.org/D2259
-
- Jul 20, 2016
-
-
Ömer Sinan Ağacan authored
Not having SCCs at the top level is becoming annoying real quick. For simplest cases, it's possible to do this transformation: f x y = ... => f = {-# SCC f #-} \x y -> ... However, it doesn't work when there's a `where` clause: f x y = <t is in scope> where t = ... => f = {-# SCC f #-} \x y -> <t is out of scope> where t = ... Or when we have a "equation style" definition: f (C1 ...) = ... f (C2 ...) = ... f (C3 ...) = ... ... (usual solution is to rename `f` to `f'` and define a new `f` with a `SCC`) This patch implements support for SCC annotations in declaration contexts. This is now a valid program: f x y = ... where g z = ... {-# SCC g #-} {-# SCC f #-} Test Plan: This passes slow validate (no new failures added). Reviewers: goldfire, mpickering, austin, bgamari, simonmar Reviewed By: bgamari, simonmar Subscribers: simonmar, thomie, mpickering Differential Revision: https://phabricator.haskell.org/D2407
-
- Jul 18, 2016
-
-
Ryan Scott authored
[ci skip]
-
- Jul 07, 2016
-
-
- Jul 06, 2016
-
-
Facundo Domínguez authored
Summary: This annotates the splice point with 'HsSpliced ref e' where 'e' is the result of the splice. 'ref' is a reference that the typechecker will fill with the local type environment. The finalizer then reads the ref and uses the local type environment, which causes 'reify' to find local variables when run in the finalizer. Test Plan: ./validate Reviewers: simonpj, simonmar, bgamari, austin, goldfire Reviewed By: goldfire Subscribers: simonmar, thomie, mboes Differential Revision: https://phabricator.haskell.org/D2286 GHC Trac Issues: #11832
-
- Jul 04, 2016
-
-
Fixes issue T12165 by banning duplicate pattern synonyms signatures. This seems to me the best solution because: 1) it is coherent with the way we treat other duplicate signatures 2) the typechecker currently doesn't try to apply a second signature to a pattern to see if it matches, probably because it assumes there is no more than one signature per object. Test Plan: ./validate Reviewers: goldfire, austin, mpickering, bgamari Reviewed By: mpickering, bgamari Subscribers: mpickering, thomie Differential Revision: https://phabricator.haskell.org/D2361 GHC Trac Issues: #12165
-
- Jul 01, 2016
-
-
This makes pattern synonym signatures more consistent with normal type signatures. Updates haddock submodule. Differential Revision: https://phabricator.haskell.org/D2083
-
- Jun 24, 2016
-
-
Simon Peyton Jones authored
This patch fixes Trac #12216 and #12127. The 'combine' function in 'imp_occ_env' in RnNames.filterImports checked for an empty field-selector list, which was (a) unnecessary and (b) wrong. I've elaborated the comments. This does NOT fix #11959 which is related but not the same (it concerns bundling of pattern synonyms).
-
- Jun 23, 2016
-
-
niteria authored
We want to remove the `Ord Unique` instance because there's no way to implement it in deterministic way and it's too easy to use by accident. We sometimes compute SCC for datatypes whose Ord instance is implemented in terms of Unique. The Ord constraint on SCC is just an artifact of some internal data structures. We can have an alternative implementation with a data structure that uses Uniquable instead. This does exactly that and I'm pleased that I didn't have to introduce any duplication to do that. Test Plan: ./validate I looked at performance tests and it's a tiny bit better. Reviewers: bgamari, simonmar, ezyang, austin, goldfire Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2359 GHC Trac Issues: #4012
-
Simon Peyton Jones authored
In reviewing the fix to Trac #12130 I found the wild-card fill-in code for ".." notation in record constructions hard to understand. It went to great contortions (including the find_tycon code) to allow data T = C { x, y :: Int } f x = C { .. } to expand to f x = C { x = x, y = y } where 'y' is an /imported function/! That seems way over the top for what record wildcards are supposed to do. So I have narrowed the record-wildcard expansion to include only /locally-bound/ variables; i.e. not top level, and certainly not imported. I don't think anyone is using record wildcards in this bizarre way, so I don't expect any fallout. Even if there is, you can easily initialise fields with eponymous but imported values by hand. An intermediate position would be to allow /local/ top-level definitions. But I doubt anyone is doing that either. Let's see if there's any fallout. It's a local change, easy to revert, so I've just gone ahead to save everyone's time.
-
Simon Peyton Jones authored
lookupGRE_Name should return either zero or one GREs, never several. This is a consequence of INVARIANT 1 on GlobalRdrEnv. So it's better if it returns a Maybe; the panic on multiple results is put in one place, instead of being scattered or ignored. Just refactoring, no change in behaviour
-
- Jun 22, 2016
-
-
Gabor Greif authored
-
- Jun 20, 2016
-
-
Simon Marlow authored
Summary: There's a precedent for special-casing $, as we already have special typing rules for it. Test Plan: validate; new test cases Reviewers: ezyang, austin, niteria, bgamari, simonpj, erikd Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2345 GHC Trac Issues: #11835
-
- Jun 18, 2016
-
-
When using TH to splice expressions involving record field construction, the parent datacon may not be in scope. We shouldn't panic about this, because we will be renaming Exact RdrNames which don't require any disambiguation. Test Plan: new test th/T12130 Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2321 GHC Trac Issues: #12130
-
- Jun 13, 2016
-
-
Simon Peyton Jones authored
This major commit was initially triggered by #11339, but it spiraled into a major review of the way in which type signatures for bindings are handled, especially partial type signatures. On the way I fixed a number of other bugs, namely #12069 #12033 #11700 #11339 #11670 The main change is that I completely reorganised the way in which type signatures in bindings are handled. The new story is in TcSigs Note [Overview of type signatures]. Some specific: * Changes in the data types for signatures in TcRnTypes: TcIdSigInfo and new TcIdSigInst * New module TcSigs deals with typechecking type signatures and pragmas. It contains code mostly moved from TcBinds, which is already too big * HsTypes: I swapped the nesting of HsWildCardBndrs and HsImplicitBndsrs, so that the wildcards are on the oustide not the insidde in a LHsSigWcType. This is just a matter of convenient, nothing deep. There are a host of other changes as knock-on effects, and it all took FAR longer than I anticipated :-). But it is a significant improvement, I think. Lots of error messages changed slightly, some just variants but some modest improvements. New tests * typecheck/should_compile * SigTyVars: a scoped-tyvar test * ExPat, ExPatFail: existential pattern bindings * T12069 * T11700 * T11339 * partial-sigs/should_compile * T12033 * T11339a * T11670 One thing to check: * Small change to output from ghc-api/landmines. Need to check with Alan Zimmerman
-
- Jun 10, 2016
-
-
Simon Peyton Jones authored
-
- Jun 06, 2016
-
-
Alan Zimmerman authored
Summary: MatchFixity was introduced to facilitate use of API Annotations. HsMatchContext does the same thing with more detail, but is chased through all over the place to provide context when processing a Match. Since we already have MatchFixity in the Match, it may as well provide the full context. updates submodule haddock Test Plan: ./validate Reviewers: austin, goldfire, bgamari Subscribers: thomie, mpickering Differential Revision: https://phabricator.haskell.org/D2271 GHC Trac Issues: #12105 (cherry picked from commit 306ecad5)
-
niteria authored
This fixes a problem described in Note [Deterministic ApplicativeDo and RecursiveDo desugaring]. Test Plan: ./validate + new testcase Reviewers: simonpj, bgamari, austin, simonmar Reviewed By: simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2287 GHC Trac Issues: #4012
-
- Jun 02, 2016
-
-
niteria authored
This change isn't necessary for determinism. appAName, choiceAName, loopAName all have pre-allocated Uniques and their relative order can't change. I opted to use nameSetElemsStable here because: * the cost is negligible * it's less fragile than just documenting Test Plan: ./validate Reviewers: simonpj, austin, bgamari, simonmar Reviewed By: simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2292 GHC Trac Issues: #4012
-
niteria authored
nameSetElems is nondeterministic and while I think we don't need determinism here it doesn't hurt. Test Plan: ./validate Reviewers: ezyang, bgamari, austin, simonmar Reviewed By: simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2293 GHC Trac Issues: #4012
-
- May 24, 2016
-
-
niteria authored
I've changed the functions to their nonDet equivalents and explained why they're OK there. This allowed me to remove foldNameSet, foldVarEnv, foldVarEnv_Directly, foldVarSet and foldUFM_Directly. Test Plan: ./validate, there should be no change in behavior Reviewers: simonpj, simonmar, austin, goldfire, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2244 GHC Trac Issues: #4012
-
- May 11, 2016
-
-
niteria authored
I've documented the guarantees that stronglyConnCompFromEdgedVertices provides and commented on the call sites to explain why they are OK from determinism standpoint. I've changed the functions to nonDetUFM versions, so that it's explicit they could introduce nondeterminism. I haven't defined container (VarSet, NameSet) specific versions, so that we have less functions to worry about. Test Plan: this is mostly just documentation, it should have no runtime effect Reviewers: bgamari, simonmar, austin, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2194 GHC Trac Issues: #4012
-
- May 10, 2016
-
-
In the long discussion on #11432, it was decided that when a type constructor is parsed as a variable ((--.->) is one example) then in order to export the type constructor then the user should be required to use the ExplicitNamespaces keyword. This was implemented in quite an indirect manner in the renamer. It is much more direct to enforce this in the parser at the expense of slighty worse error messages. Further to this, the check in the renamer was actually slightly wrong. If the variable was in scope then no error was raised, this was causing panics, see #12026 for an example. Reviewers: austin, bgamari Subscribers: davean, skvadrik, thomie Differential Revision: https://phabricator.haskell.org/D2181 GHC Trac Issues: #12026
-
- May 02, 2016
-
-
Facundo Domínguez authored
Summary: With this patch closed variables are allowed regardless of whether they are bound at the top level or not. The FloatOut pass is always performed. When optimizations are disabled, only expressions that go to the top level are floated. Thus, the applications of the StaticPtr data constructor are always floated. The CoreTidy pass makes sure the floated applications appear in the symbol table of object files. It also collects the floated bindings and inserts them in the static pointer table. The renamer does not check anymore if free variables appearing in the static form are top-level. Instead, the typechecker looks at the tct_closed flag to decide if the free variables are closed. The linter checks that applications of StaticPtr only occur at the top of top-level bindings after the FloatOut pass. The field spInfoName of StaticPtrInfo has been removed. It used to contain the name of the top-level binding that contains the StaticPtr application. However, this information is no longer available when the StaticPtr is constructed, as the binding name is determined now by the FloatOut pass. Test Plan: ./validate Reviewers: goldfire, simonpj, austin, hvr, bgamari Reviewed By: simonpj Subscribers: thomie, mpickering, mboes Differential Revision: https://phabricator.haskell.org/D2104 GHC Trac Issues: #11656
-
- Apr 28, 2016
-
-
niteria authored
There are couple of places where we do `foldUniqSet` just to compute `any` or `all`. `foldUniqSet` is non-deterministic in the general case and `any` and `all` also read nicer. Test Plan: ./validate Reviewers: simonmar, goldfire, simonpj, bgamari, austin Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2156 GHC Trac Issues: #4012
-
Simon Peyton Jones authored
This patch uses the named fields of * FieldLabel * RecordPatSynField in construction and pattern matching. The fields existed before, but we were often using positional notation. Also a minor refactor of the API of mkPatSynRecSelBinds No change in functionality
-
Simon Peyton Jones authored
-
- Apr 22, 2016
-
-
Simon Peyton Jones authored
Now that warnIf takes a "reason", we can test the reason in warnIf rather than in the caller. Less code, and less risk of getting the test and the reason out of sync.
-
- Apr 20, 2016
-
-
Simon Peyton Jones authored
This big patch is in pursuit of Trac #11348. It is largely the work of Alex Veith (thank you!), with some follow-up simplification and refactoring from Simon PJ. The main payload is described in RnSource Note [Dependency analysis of type, class, and instance decls] which is pretty detailed. * There is a new data type HsDecls.TyClGroup, for a strongly connected component of type/class/instance/role decls. The hs_instds field of HsGroup disappears, in consequence This forces some knock-on changes, including a minor haddock submodule update Smaller, weakly-related things * I found that both the renamer and typechecker were building an identical env for RoleAnnots, so I put common code for RoleAnnotEnv in RnEnv. * I found that tcInstDecls1 had very clumsy error handling, so I put it together into TcInstDcls.doClsInstErrorChecks
-
- Apr 19, 2016
-
-
Simon Peyton Jones authored
This patch finishes off Trac #11450. Following debate on that ticket, the patch tightens up the rules for what the instances of an associated type can look like. Now they must match the instance header exactly. Eg class C a b where type T a x b With this class decl, if we have an instance decl instance C ty1 ty2 where ... then the type instance must look like type T ty1 v ty2 = ... with exactly - 'ty1' for 'a' - 'ty2' for 'b', and - a variable for 'x' For example: instance C [p] Int type T [p] y Int = (p,y,y) Previously we allowed multiple instance equations and now, in effect, we don't since they would all overlap. If you want multiple cases, use an auxiliary type family. This is consistent with the treatment of generic-default instances, and the user manual always said "WARNING: this facility (multiple instance equations may be withdrawn in the future". I also improved error messages, and did other minor refactoring.
-
- Apr 12, 2016
-
-
Richard Eisenberg authored
Previously, I had forgotten to omit variables already in scope from the TypeInType CUSK check. Simple enough to fix. Test case: typecheck/should_compile/T11811
-
- Apr 10, 2016
-
-
When the typechecker generates the error message for an out-of-scope variable, it now uses the GlobalRdrEnv with respect to which the variable is unbound, not the GlobalRdrEnv which is available at the time the error is reported. Doing so ensures we do not provide suggestions which themselves are out-of-scope (because they are bound in a later inter-splice group). Nonetheless, we do note in the error message if an unambiguous, exact match to the out-of-scope variable is found in a later inter-splice group, and we specify where that match is not in scope. Test Plan: ./validate Reviewers: goldfire, austin, bgamari Reviewed By: goldfire Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2000 GHC Trac Issues: #11680
-
Record selectors of data types spliced in with Template Haskell are not renamer-resolved correctly in GHC HEAD. The culprit is `newRecordSelector` which violates notes `Note [Binders in Template Haskell] in Convert.hs` and `Note [Looking up Exact RdrNames] in RnEnv.hs`. This commit fixes `newRecordSelector` accordingly. Test Plan: ./validate Reviewers: thomie, mpickering, bgamari, austin, simonpj, goldfire Reviewed By: goldfire Differential Revision: https://phabricator.haskell.org/D2091 GHC Trac Issues: #11809
-
- Apr 05, 2016
-
-
This fixes a bug where warnings actually controlled by - `Opt_WarnUnusedMatches` - `Opt_WarnUnusedTypePatterns` - `Opt_WarnUnusedTopBinds` were incorrectly reported as being controlled by `Opt_WarnUnusedLocalBinds` as well This bug was introduced in bb5afd3c while implementing #10752 Test Plan: ./validate still running -- testsuite output wiggles expected Reviewers: barrucadu, quchen, austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2077
-